Difference between revisions of "Chaitin's construction"

From HaskellWiki
Jump to navigation Jump to search
m (→‎Decoding: Changing term ``arrow parsers'' into a link to Arrow#Parser)
(Not so important details come to a new Chaitin's construction/Parser page. Parsers are not necessary here, a good generator is enough)
Line 25: Line 25:
   
 
Having seen this, decoding is rather straightforward.
 
Having seen this, decoding is rather straightforward.
  +
[[/Parser|Here is a parser]] for illustration, but it serves only didactical purposes: it will not be used in the final implementation, because a good term geerator makes parsing superfluous at this task.
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 [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 ====
 
 
<haskell>
 
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
 
</haskell>
 
 
==== Combinatory logic term modules ====
 
 
===== 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 ====
 
 
===== Binary tree =====
 
 
<haskell>
 
module Tree (Tree (Leaf, Branch)) where
 
 
data Tree a = Leaf a | Branch (Tree a) (Tree a)
 
</haskell>
 
 
===== Parser =====
 
 
<haskell>
 
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
 
</haskell>
 
 
===== Prelude extension =====
 
 
<haskell>
 
module PreludeExt (bool) where
 
 
bool :: a -> a -> Bool -> a
 
bool thenC elseC t = if t then thenC else elseC
 
</haskell>
 
   
 
=== Approach based on decoding with partial function ===
 
=== Approach based on decoding with partial function ===

Revision as of 12:41, 4 August 2006

Introduction

Are there any real numbers which are defined exactly, but cannot be computed? This question leads us to exact real arithmetic, foundations of mathematics and computer science.

See Wikipedia article on Chaitin's construction, referring to e.g.

Basing it on combinatory logic

Some more direct relatedness to functional programming: we can base on combinatory logic (instead of a Turing machine).

Coding

See the prefix coding system described in Binary Lambda Calculus and Combinatory Logic (page 20) written by John Tromp:

of course, , are meta-variables, and also some other notations are changed slightly.

Decoding

Having seen this, decoding is rather straightforward. Here is a parser for illustration, but it serves only didactical purposes: it will not be used in the final implementation, because a good term geerator makes parsing superfluous at this task.

Approach based on decoding with partial function

Now, Chaitin's construction will be here

where

should denote an unary predicate “has normal form” (“terminates”)
should mean an operator “decode” (a function from finite bit sequences to combinatory logic terms)
should denote the set of all finite bit sequences
should denote the set of syntactically correct bit sequences (semantically, they may either terminate or diverge), i.e. the domain of the decoding function, i.e. the range of the coding function. Thus,
“Absolute value”
should mean the length of a bit sequence (not combinatory logic term evaluation!)

Approach based on decoding with total function

Seen above, was a partial function (from finite bit sequences). 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).

If this is confusing or annoying, then we can choose a more Haskell-like 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.

Related concepts

To do

Writing a program in Haskell -- or in combinatory logic:-) -- which could help in making conjectures on combinatory logic-based Chaitin's constructions. It would make only approximations, in a similar way that most Mandelbrot plotting softwares work: it would ask for a maximum limit of iterations.

chaitin --computation=cl --coding=tromp --limit-of-iterations=5000 --digits=10 --decimal