Chaitin's construction/Parser

From HaskellWiki
< Chaitin's construction
Revision as of 12:44, 4 August 2006 by EndreyMark (talk | contribs) (Receiving contents from the mentioned page, and adjusting its section hierarchy)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to navigation Jump to search

Let us describe the seen language with a LL(1) grammar, and let us make use of the lack of backtracking, lack of look-ahead, when deciding which parser approach to use.

Some notes about the used parser library: I shall use the didactical approach read in paper Monadic Parser Combinators (written by Graham Hutton and Erik Meier). The optimalisations described in the paper are avoided here. Of course, we can make optimalisations, or choose sophisticated parser libraries (Parsec, arrow parsers). A pro for this simpler parser: it may be easier to augment it with other monad transformers. But, I think, the task does not require such ability. So the real pro for it is that it looks more didactical for me. Of couse, it may be inefficient at many other tasks, but I hope, the LL(1) grammar will not raise huge problems.

Decoding module

 module Decode (clP) where

 import Parser (Parser, item)
 import CL (CL, k, s, apply)
 import CLExt ((>>@))
 import PreludeExt (bool)

 clP :: Parser Bool CL
 clP = item >>= bool applicationP baseP

 applicationP :: Parser Bool CL
 applicationP = clP >>@ clP

 baseP :: Parser Bool CL
 baseP = item >>= bool k s

 kP, sP :: Parser Bool CL
 kP = return k
 sP = return s

Combinatory logic term modules

CL

 module CL (CL, k, s, apply) where

 import Tree (Tree (Leaf, Branch))
 import BaseSymbol (BaseSymbol, kay, ess)

 type CL = Tree BaseSymbol 

 k, s :: CL
 k = Leaf kay
 s = Leaf ess

 apply :: CL -> CL -> CL
 apply = Branch

CL extension

 module CLExt ((>>@)) where

 import CL (CL, apply)
 import Control.Monad (Monad, liftM2)

 (>>@) :: Monad m => m CL -> m CL -> m CL
 (>>@) = liftM2 apply

Base symbol

 module BaseSymbol (BaseSymbol, kay, ess) where

 data BaseSymbol = K | S

 kay, ess :: BaseSymbol
 kay = K
 ess = S

Utility modules

Binary tree

 module Tree (Tree (Leaf, Branch)) where

 data Tree a = Leaf a | Branch (Tree a) (Tree a)

Parser

 module Parser (Parser, runParser, item) where

 import Control.Monad.State (StateT, runStateT, get, put)

 type Parser token a = StateT [token] [] a

 runParser :: Parser token a -> [token] -> [(a, [token])]
 runParser = runStateT

 item :: Parser token token
 item = do
 	token : tokens <- get
 	put tokens
 	return token

Prelude extension

 module PreludeExt (bool) where

 bool :: a -> a -> Bool -> a
 bool thenC elseC t = if t then thenC else elseC