a0e93627a744547ed105776595d534bc9a6d6a76
[clean-tests.git] / datatype / Main.hs
1 {-# LANGUAGE TemplateHaskell #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE QuasiQuotes #-}
4 module Main where
5
6 import Language
7
8 import Compiler
9 import Printer
10 import Interpreter
11 import Language.Quote
12
13 import Tuple
14
15 main :: IO ()
16 main
17 = putStrLn (show $ interpret 10 <$> runCompiler (e1))
18 -- >> putStrLn (show $ interpret 10 <$> runCompiler (tuplef0' e1))
19 -- >> putStrLn (show $ interpret 10 <$> runCompiler (tuplef1' e1))
20 -- >> putStrLn (show $ interpret 10 <$> runCompiler (tuplef1' $ second' e3))
21 -- >> putStrLn (runPrint $ lit (42 :: Int) `cons` (lit (10 :: Int) `cons` nil))
22 -- >> putStrLn (show $ interpret 20 <$> runCompiler (isNil $ lit (38 :: Int) `cons` nil))
23 -- >> putStrLn (runPrint $ unmain $ f0)
24 -- >> putStrLn (show $ runCompiler (unmain f0))
25 -- >> putStrLn (show $ interpret 20 <$> runCompiler (unmain f0))
26 -- >> putStrLn (show $ runCompiler (unmain f1))
27 -- >> putStrLn (show $ interpret 20 <$> runCompiler (unmain f1))
28 -- >> putStrLn (show $ runCompiler (unmain f2))
29 -- >> putStrLn (show $ interpret 20 <$> runCompiler (unmain f2))
30 -- >> putStrLn (show $ runCompiler (unmain f3))
31 -- >> putStrLn (show $ interpret 20 <$> runCompiler (unmain f3))
32 -- >> putStrLn (show $ runCompiler (unmain f4))
33 -- >> putStrLn (show $ interpret 100 <$> runCompiler (unmain f4))
34 -- >> putStrLn (show $ runInterpreter (unmain f2))
35 -- >> putStrLn (show $ runInterpreter (unmain f4))
36 >> putStrLn (runPrint $ unmain f5)
37 >> putStrLn (show $ interpret 50 <$> runCompiler (unmain f5))
38
39 e0 :: Expression v => v Int
40 e0 = lit 2 ^. lit 8
41
42 e1 :: (Expression v, Tuple' v) => v (Tuple Char Int)
43 e1 = tuple (lit 'c') (lit 42)
44
45 e1' :: (Expression v, Tuple' v) => v Char
46 e1' = tuplef0' e1
47
48 e1'' :: (Expression v, Tuple' v) => v Int
49 e1'' = tuplef1' e1
50
51 e2 :: (Expression v, TupleR' v) => v (TupleR Char Bool)
52 e2 = tupler (lit 'c') (lit True)
53
54 e3 :: (Expression v, Tuple' v, TupleR' v) => v (TupleR Char (Tuple Int Bool))
55 e3 = tupler (lit 'c') (tuple (lit 42) (lit True))
56
57 f0 :: (Expression v, Function () v) => Main (v Int)
58 f0
59 = fun ( \c42->(\()->lit 42)
60 :- Main {unmain=c42 () +. lit 38}
61 )
62
63 f1 :: (Expression v, Function (v Int) v, Function () v) => Main (v Int)
64 f1
65 = fun ( \c42->(\()->lit 42)
66 :- fun ( \inc->(\i->i +. lit 1)
67 :- Main {unmain=c42 () +. inc (lit 41)}
68 ))
69
70 f2 :: (Expression v, Function (v Int, v Int) v) => Main (v Int)
71 f2
72 = fun ( \sub->(\(x, y)->x -. y)
73 :- Main {unmain=sub (lit 2, lit 8)}
74 )
75
76 f3 :: (Expression v, Tuple' v, Function (v Int) v) => Main (v (Tuple Int Int))
77 f3
78 = fun ( \idfun->(\x->x)
79 :- Main {unmain=tuple (idfun (lit 42)) (idfun (lit 4)) }
80 )
81
82 f4 :: (Expression v, Function (v Int) v) => Main (v Int)
83 f4
84 = fun ( \fac->(\i->if' (i ==. lit 0) (lit 1) (i *. fac (i -. lit 1)))
85 :- Main {unmain=fac (lit 10)}
86 )
87
88 f5 :: (List' v, Expression v, Function (v (List Int)) v) => Main (v Int)
89 f5
90 = fun ( \sum->(\l->[cp|case l of
91 Cons e rest -> e +. sum rest
92 _ -> 0
93 |])
94 :- Main {unmain=sum $ lit (1 :: Int) `cons` (lit 2 `cons` (lit 3 `cons` nil))}
95 )