Difference between revisions of "Chaitin's construction"

From HaskellWiki
Jump to navigation Jump to search
m (Putting verb in a sentence which consisted only of a huge noun phrase)
(Defining decode function in Haskell)
Line 12: Line 12:
 
== Basing it on combinatory logic ==
 
== Basing it on combinatory logic ==
   
Some more direct relatedness to functional programming: we can base <math>\Omega</math> on [[combinatory logic]] (instead of a [[Turing machine]]), see the prefix coding system described in [http://homepages.cwi.nl/~tromp/cl/cl.html Binary Lambda Calculus and Combinatory Logic] (page 20) written by John Tromp:
+
Some more direct relatedness to functional programming: we can base <math>\Omega</math> on [[combinatory logic]] (instead of a [[Turing machine]]).
  +
  +
=== Coding ===
  +
  +
See the prefix coding system described in [http://homepages.cwi.nl/~tromp/cl/cl.html Binary Lambda Calculus and Combinatory Logic] (page 20) written by John Tromp:
 
:<math>\widehat{\mathbf S} \equiv 00</math>
 
:<math>\widehat{\mathbf S} \equiv 00</math>
 
:<math>\widehat{\mathbf K} \equiv 01</math>
 
:<math>\widehat{\mathbf K} \equiv 01</math>
 
:<math>\widehat{\left(x y\right)} \equiv 1 \widehat x \widehat y</math>
 
:<math>\widehat{\left(x y\right)} \equiv 1 \widehat x \widehat y</math>
 
of course, <math>c</math>, <math>d</math> are meta-variables, and also some other notations are changed slightly.
 
of course, <math>c</math>, <math>d</math> are meta-variables, and also some other notations are changed slightly.
  +
  +
=== Decoding ===
  +
  +
Having seen this, decoding is rather straightforward.
  +
Let us represent it e.g with the following LL1 parser. Of course, we can build it on top of more sophisticated parser libraries (Parsec, arrow parsers)
  +
  +
==== Decoding module ====
  +
  +
<haskell>
  +
module Decode (clP) where
  +
  +
import Parser (Parser, item)
  +
import CL (CL, k, s, apply)
  +
import CLExt ((>>^))
  +
  +
clP :: Parser Bool CL
  +
clP = item (bool applicationP baseP)
  +
  +
applicationP :: Parser Bool CL
  +
applicationP = item (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 Control.Monad (Monad, liftM2)
  +
  +
(>>^) :: 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 where
  +
  +
data Tree a = Leaf a | Branch (Tree a) (Tree a)
  +
</haskell>
  +
  +
===== Parser =====
  +
  +
<haskell>
  +
module Parser (Parser, item) where
  +
  +
type Parser token a = StateT [token] [] a
  +
  +
item :: Parser a
  +
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>
  +
  +
=== Partial function approach ===
   
 
Now, Chaitin's construction will be here
 
Now, Chaitin's construction will be here
Line 31: Line 140:
 
;“Absolute value”
 
;“Absolute value”
 
:should mean the length of a bit sequence (not [[combinatory logic]] term evaluation!)
 
:should mean the length of a bit sequence (not [[combinatory logic]] term evaluation!)
  +
  +
=== Total function approach ===
   
 
Here, <math>\mathrm{dc}</math> is a partial function (from finite bit sequences). If this is confusing or annoying, then we can choose a more Haskell-like approach, making <math>\mathrm{dc}</math> a total function:
 
Here, <math>\mathrm{dc}</math> is a partial function (from finite bit sequences). If this is confusing or annoying, then we can choose a more Haskell-like approach, making <math>\mathrm{dc}</math> a total function:

Revision as of 16:48, 3 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. Let us represent it e.g with the following LL1 parser. Of course, we can build it on top of more sophisticated parser libraries (Parsec, arrow parsers)

Decoding module

 module Decode (clP) where

 import Parser (Parser, item)
 import CL (CL, k, s, apply)
 import CLExt ((>>^))

 clP :: Parser Bool CL
 clP = item (bool applicationP baseP)

 applicationP :: Parser Bool CL
 applicationP = item (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 Control.Monad (Monad, liftM2)

 (>>^) :: 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 where

 data Tree a = Leaf a | Branch (Tree a) (Tree a)
Parser
 module Parser (Parser, item) where

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

 item :: Parser a
 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

Partial function approach

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!)

Total function approach

Here, is a partial function (from finite bit sequences). If this is confusing or annoying, then we can choose a more Haskell-like approach, making a total function:

 dc :: [Bit] -> Maybe CL

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