hnock

A Nock interpreter.
git clone git://git.jtobin.io/hnock.git
Log | Files | Refs | README | LICENSE

Main.hs (2227B)


      1 module Main where
      2 
      3 import Nock
      4 
      5 -- /[3 [[4 5] [6 14 15]]]
      6 -- should be [6 [14 15]]
      7 expr0 :: Expr
      8 expr0 =
      9   Net
     10     (Cell (Atom 3)
     11       (Cell (Cell (Atom 4) (Atom 5))
     12         (Cell (Atom 6) (Cell (Atom 14) (Atom 15)))))
     13 
     14 noun0 :: Noun
     15 noun0 = Cell (Atom 6) (Cell (Atom 14) (Atom 15))
     16 
     17 -- *[[[4 5] [6 14 15]] [0 7]]
     18 -- should be [14 15]
     19 expr1 :: Expr
     20 expr1 =
     21   Tar
     22     (Cell
     23       (Cell (Cell (Atom 4) (Atom 5))
     24         (Cell (Atom 6) (Cell (Atom 14) (Atom 15))))
     25       (Cell (Atom 0) (Atom 7)))
     26 
     27 noun1 :: Noun
     28 noun1 = Cell (Atom 14) (Atom 15)
     29 
     30 -- *[42 [1 153 218]]
     31 -- should be [153 218]
     32 expr2 :: Expr
     33 expr2 =
     34   Tar
     35     (Cell (Atom 42)
     36       (Cell (Atom 1) (Cell (Atom 153) (Atom 218))))
     37 
     38 noun2 :: Noun
     39 noun2 = Cell (Atom 153) (Atom 218)
     40 
     41 -- *[57 [4 0 1]]
     42 -- should be 58
     43 expr3 :: Expr
     44 expr3 =
     45   Tar
     46     (Cell (Atom 57)
     47       (Cell (Atom 4)
     48         (Cell (Atom 0) (Atom 1))))
     49 
     50 noun3 :: Noun
     51 noun3 = Atom 58
     52 
     53 -- *[[132 19] [4 0 3]]
     54 -- should be 20
     55 expr4 :: Expr
     56 expr4 =
     57   Tar
     58     (Cell (Cell (Atom 132) (Atom 19))
     59       (Cell (Atom 4)
     60         (Cell (Atom 0) (Atom 3))))
     61 
     62 noun4 :: Noun
     63 noun4 = Atom 20
     64 
     65 -- /[7 [[4 5] [6 14 15]]]
     66 -- should be [14 15]
     67 expr5 :: Expr
     68 expr5 =
     69   Net
     70     (Cell (Atom 7)
     71       (Cell (Cell (Atom 4) (Atom 5))
     72         (Cell (Atom 6) (Cell (Atom 14) (Atom 15)))))
     73 
     74 noun5 :: Noun
     75 noun5 = Cell (Atom 14) (Atom 15)
     76 
     77 -- *[77 [2 [1 42] [1 1 153 218]]]
     78 -- should be [153 218]
     79 expr6 :: Expr
     80 expr6 =
     81   Tar
     82     (Cell (Atom 77)
     83       (Cell (Atom 2)
     84         (Cell (Cell (Atom 1) (Atom 42))
     85           (Cell (Atom 1)
     86             (Cell (Atom 1)
     87               (Cell (Atom 153) (Atom 218)))))))
     88 
     89 noun6 :: Noun
     90 noun6 = Cell (Atom 153) (Atom 218)
     91 
     92 -- #[4 11 [[22 33] 44]]
     93 -- should be [[11 33] 44]
     94 expr7 :: Expr
     95 expr7 =
     96   Hax
     97     (Cell (Atom 4)
     98       (Cell (Atom 11)
     99         (Cell (Cell (Atom 22) (Atom 33)) (Atom 44))))
    100 
    101 noun7 :: Noun
    102 noun7 = Cell (Cell (Atom 11) (Atom 33)) (Atom 44)
    103 
    104 main :: IO ()
    105 main = do
    106   print (fmap (== noun0) (eval expr0))
    107   print (fmap (== noun1) (eval expr1))
    108   print (fmap (== noun2) (eval expr2))
    109   print (fmap (== noun3) (eval expr3))
    110   print (fmap (== noun4) (eval expr4))
    111   print (fmap (== noun5) (eval expr5))
    112   print (fmap (== noun6) (eval expr6))
    113   print (fmap (== noun7) (eval expr7))
    114