Chaitin's construction/Parser
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[edit]
Decoding module[edit]
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[edit]
See [[../Combinatory logic | combinatory logic term modules here]].
Utility modules[edit]
Binary tree[edit]
module Tree (Tree (Leaf, Branch)) where
data Tree a = Leaf a | Branch (Tree a) (Tree a)
Parser[edit]
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[edit]
module PreludeExt (bool) where
bool :: a -> a -> Bool -> a
bool thenC elseC t = if t then thenC else elseC
Using this parser for decoding[edit]
Approach based on decoding with partial function[edit]
Seen above, Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \mathrm{dc}} 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[edit]
If this is confusing or annoying, then we can choose another approach, making Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \mathrm{dc}} 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
- Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \sum_{p\in 2^*,\;\mathrm{maybe}\;\downarrow\;\mathrm{hnf}\;\left(\mathrm{dc}\;p\right)} 2^{-\left|p\right|}}
where Failed to parse (SVG (MathML can be enabled via browser plugin): Invalid response ("Math extension cannot connect to Restbase.") from server "https://wikimedia.org/api/rest_v1/":): {\displaystyle \downarrow} should denote false truth value.
Term generators instead of parsers[edit]
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.