aboutsummaryrefslogtreecommitdiffhomepage
path: root/src/Lib.hs
blob: 698c0ae9c47ca29200625ab5ff823413a6ed5e4a (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
{-# LANGUAGE LambdaCase #-}

module Lib
  ( fromJottary
  , s
  , k
  , i
  ) where

import           Control.Monad                  ( replicateM )
import           Debug.Trace                    ( trace )
import           Term

s :: Term
s = Abs (Abs (Abs (App (App (Idx 2) (Idx 0)) (App (Idx 1) (Idx 0)))))

k :: Term
k = Abs (Abs (Idx 1))

i :: Term
i = Abs (Idx 0)

count :: String -> Int
count (x : xs) | x == '1'  = 1 + count xs
               | otherwise = count xs
count [] = 0

fromDecimalJottary :: Int -> Term
fromDecimalJottary p = foldr1 App (reverse (gen !! p) ++ [i])
 where
  lio = Abs (App (App (Idx 0) s) k)
  rio = Abs (App s (App k (Idx 0)))
  gen = [0 ..] >>= (`replicateM` [lio, rio])

fromJottary :: String -> Term
fromJottary t = trace (show $ count t) (fromDecimalJottary $ count t)