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

From HaskellWiki
Jump to navigation Jump to search
(Receiving contents from the mentioned page, and adjusting its section hierarchy)
 
(Moving text and modifying section hierarchy. Mentioning term generators)
Line 5: Line 5:
 
Some notes about the used parser library: I shall use the didactical approach read in paper [http://www.cs.nott.ac.uk/~gmh/bib.html#monparsing Monadic Parser Combinators] (written by [http://www.cs.nott.ac.uk/Department/Staff/gmh/ 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#Parser|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.
 
Some notes about the used parser library: I shall use the didactical approach read in paper [http://www.cs.nott.ac.uk/~gmh/bib.html#monparsing Monadic Parser Combinators] (written by [http://www.cs.nott.ac.uk/Department/Staff/gmh/ 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#Parser|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 ==
+
== Decoding function illustrated as a parser ==
  +
  +
=== Decoding module ===
   
 
<haskell>
 
<haskell>
Line 29: Line 31:
 
</haskell>
 
</haskell>
   
== Combinatory logic term modules ==
+
=== Combinatory logic term modules ===
   
=== CL ===
+
==== CL ====
   
 
<haskell>
 
<haskell>
Line 49: Line 51:
 
</haskell>
 
</haskell>
   
=== CL extension ===
+
==== CL extension ====
   
 
<haskell>
 
<haskell>
Line 61: Line 63:
 
</haskell>
 
</haskell>
   
=== Base symbol ===
+
==== Base symbol ====
   
 
<haskell>
 
<haskell>
Line 73: Line 75:
 
</haskell>
 
</haskell>
   
== Utility modules ==
+
=== Utility modules ===
   
=== Binary tree ===
+
==== Binary tree ====
   
 
<haskell>
 
<haskell>
Line 83: Line 85:
 
</haskell>
 
</haskell>
   
=== Parser ===
+
==== Parser ====
   
 
<haskell>
 
<haskell>
Line 102: Line 104:
 
</haskell>
 
</haskell>
   
=== Prelude extension ===
+
==== Prelude extension ====
   
 
<haskell>
 
<haskell>
Line 110: Line 112:
 
bool thenC elseC t = if t then thenC else elseC
 
bool thenC elseC t = if t then thenC else elseC
 
</haskell>
 
</haskell>
  +
  +
== Using this parser for decoding ==
  +
  +
=== Approach based on decoding with partial function ===
  +
  +
Seen above, <math>\mathrm{dc}</math> was a partial function (from finite bit sequences to [[combinatory logic]] terms). We can implement it e.g. as
  +
<haskell>
  +
dc :: [Bit] -> CL
  +
dc = fst . head . runParser clP
  +
</haskell>
  +
where the use of <hask>head</hask> 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 <math>\mathrm{dc}</math> a total function:
  +
<haskell>
  +
dc :: [Bit] -> Maybe CL
  +
dc = fst . head . runParser (neverfailing clP)
  +
</haskell>
  +
where
  +
<haskell>
  +
neverfailing :: MonadPlus m => m a -> m (Maybe a)
  +
neverfailing p = liftM Just p `mplus` return Nothing
  +
</haskell>
  +
then, Chaitin's construction will be
  +
:<math>\sum_{p\in 2^*,\;\mathrm{maybe}\;\downarrow\;\mathrm{hnf}\;\left(\mathrm{dc}\;p\right)} 2^{-\left|p\right|}</math>
  +
where <math>\downarrow</math> 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.
  +
  +
  +
  +
[[Category:Theoretical foundations]]

Revision as of 13:11, 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

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

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.