Difference between revisions of "Chaitin's construction/Parser"

From HaskellWiki
Jump to navigation Jump to search
(Moving text and modifying section hierarchy. Mentioning term generators)
(Moving combinatory logic term modules to a separate pege)
 
Line 33: Line 33:
 
=== Combinatory logic term modules ===
 
=== Combinatory logic term modules ===
   
  +
See [[../Combinatory logic | combinatory logic term modules here]].
==== CL ====
 
 
<haskell>
 
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
 
</haskell>
 
 
==== CL extension ====
 
 
<haskell>
 
module CLExt ((>>@)) where
 
 
import CL (CL, apply)
 
import Control.Monad (Monad, liftM2)
 
 
(>>@) :: Monad m => m CL -> m CL -> m CL
 
(>>@) = liftM2 apply
 
</haskell>
 
 
==== Base symbol ====
 
 
<haskell>
 
module BaseSymbol (BaseSymbol, kay, ess) where
 
 
data BaseSymbol = K | S
 
 
kay, ess :: BaseSymbol
 
kay = K
 
ess = S
 
</haskell>
 
   
 
=== Utility modules ===
 
=== Utility modules ===

Latest revision as of 14:31, 4 August 2006

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 function illustrated as a parser

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

See combinatory logic term modules here.

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

Using this parser for decoding

Approach based on decoding with partial function

Seen above, was a partial function (from finite bit sequences to combinatory logic terms). We can implement it e.g. as

dc :: [Bit] -> CL
dc = fst . head . runParser clP

where the use of head reveals that it is a partial function (of course, because not every bit sequence is a correct coding of a CL-term).

Approach based on decoding with total function

If this is confusing or annoying, then we can choose another approach, making a total function:

 dc :: [Bit] -> Maybe CL
 dc = fst . head . runParser (neverfailing clP)

where

 neverfailing :: MonadPlus m => m a -> m (Maybe a)
 neverfailing p = liftM Just p `mplus` return Nothing

then, Chaitin's construction will be

where should denote false truth value.

Term generators instead of parsers

All these are illustrations -- they will not be present in the final application. The real software will use no parsers at all -- it will use term generators instead. It will generate directly “all” combinatory logic terms in an “ascending length” order, attribute “length” to them, and approximating Chaitin's construct this way. It will not use strings / bit sequences at all: it will handle combinatory logic-terms directly.