[Haskell-cafe] TT check

Miguel Mitrofanov miguelimo38 at yandex.ru
Sun Jul 1 15:07:09 EDT 2007


Hi Andrew!

Seems that you've made a typo or something...

> module Term where
> import Control.Monad.State
> testData = "*****X*X*X*XX**X*X*XX*X*X*X*XX*X*X*XX***X*X*X*XX" ++
>            "***X*X*X*XX**X*X*XX*X*X*X*XX*X*X*XX*XX***X*X*X*X" ++
>            "X***X*X*X*XX**X*X*XX*X*X*X*XX*X*X*XX*XX"
> data Term = IntTerm Int | Term (Term -> Term)
> inc = Term $ \x -> case x of IntTerm n -> IntTerm (n+1)
> out x = case x of IntTerm n -> n
> outCh x = out $ x `apply` inc `apply` IntTerm 0
> apply x y = case x of Term f -> f y
> infixl `apply`
> xComb = Term $ \x -> x `apply` sComb `apply` kComb
> kComb = Term $ \x -> Term $ \y -> x
> sComb = Term $ \f -> Term $ \g -> Term $ \x -> f `apply` x `apply` (g `apply` x)
> decode = evalState decodeS where
>     decodeS = do c:cs <- get
>                  put cs
>                  case c of 'X' -> return xComb
>                            '*' -> do f <- decodeS
>                                      x <- decodeS
>                                      return $ f `apply` x

Then
    outCh $ decode testData
prints "4", as desired, while your version simply fails.

AC> Can somebody check that I've implemented this correctly?

AC> *****X*X*X*XX***X*X*XXX*X*X*XX***X*X*X*XX**X*X*XX**X*X*X*XX
AC> ***X*X*XXX*X*X*XX**XX*X*XX***X*X*XXX*X*XX****X*X*X*XX****X*
AC> X*X*XX***X*X*XXX*X*X*XXX*X*XXXX****X*X*XXX****X*X*X*XX***X*
AC> X*XXX*X*X*XXX*X*XXXX

AC> A parser for this is given by

AC>   decode (c:cs) = case c of
AC>     'X' -> X
AC>     '*' -> let (e0,cs0) = decode cs; (e1,cs1) = decode cs0 in (e0 
AC> `apply` e1, cs1)

AC> The letter X stands for the following combinator:

AC>   X = \x -> xSK
AC>   K = \xy -> x
AC>   S = \fgx -> fx(gx)



More information about the Haskell-Cafe mailing list