ushalow
[clean-tests.git] / old / afp / a8 / a8.icl
1 module a8
2
3 /*
4 Advanced Progrmming 2018, Assignment 8
5 Pieter Koopman, pieter@cs.ru.nl
6 */
7 import StdEnv
8
9 import iTasks => qualified return, >>=, >>|, sequence, forever, :: Set
10
11 import Control.Applicative
12 import Control.Monad
13 import Control.Monad.State
14 import Control.Monad.Trans
15 import Data.Func
16 import Data.Functor
17 import Data.Either
18 import Data.Maybe
19
20 import Text => qualified join
21
22 import qualified Data.List as List
23 import qualified Data.Map as Map
24
25 :: Expression
26 = New [Int]
27 | Elem Int
28 | Variable Ident
29 | Size Set
30 | (+.) infixl 6 Expression Expression
31 | (-.) infixl 6 Expression Expression
32 | (*.) infixl 7 Expression Expression
33 | (=.) infixl 2 Ident Expression
34
35 :: Logical
36 = TRUE | FALSE
37 | (In) infix 4 Elem Set
38 | (==.) infix 4 Expression Expression
39 | (<=.) infix 4 Expression Expression
40 | Not Logical
41 | (||.) infixr 2 Logical Logical
42 | (&&.) infixr 3 Logical Logical
43
44 :: Stmt
45 = Expression Expression
46 | Logical Logical
47 | For Ident Set Stmt
48 | If Logical Stmt Stmt
49
50 :: Set :== Expression
51 :: Elem :== Expression
52 :: Ident :== String
53
54 // === State
55 :: Val :== Either Int [Int]
56 :: SemState :== 'Map'.Map String Val
57 :: Sem a :== StateT SemState (Either String) a
58
59 store :: Ident Val -> Sem Val
60 store k v = modify ('Map'.put k v) *> pure v
61
62 read :: Ident -> Sem Val
63 read k = gets ('Map'.get k) >>= maybe (fail "Unknown ident") pure
64
65 fail :: String -> Sem a
66 fail s = liftT (Left s)
67
68 // === semantics
69 isset :: (Sem Val) -> Sem [Int]
70 isset s = s >>= either (\_->fail "Expected Set, got Elem") pure
71
72 iselem :: (Sem Val) -> Sem Int
73 iselem s = s >>= either pure (\_->fail "Expected Elem, got Set")
74
75 class eval t ~v :: t -> Sem v
76
77 instance eval Expression Val
78 where
79 eval :: Expression -> Sem Val
80 eval (New s) = pure $ Right s
81 eval (Elem i) = pure $ Left i
82 eval (Variable i) = read i
83 eval (Size s) = isset (eval s) >>= pure o Left o length
84 eval (l +. r) = eval l >>= \x->eval r >>= \y->case (x, y) of
85 (Left x, Left y) = pure $ Left (x + y)
86 (Left x, Right y) = pure $ Right $ 'List'.union [x] y
87 (Right x, Left y) = pure $ Right $ 'List'.union x [y]
88 (Right x, Right y) = pure $ Right $ 'List'.union x y
89 eval (l -. r) = eval l >>= \x->eval r >>= \y->case (x, y) of
90 (Left x, Left y) = pure $ Left (x - y)
91 (Left x, Right y) = fail "Elem -. Set is illegal"
92 (Right x, Left y) = pure $ Right $ 'List'.intersect x [y]
93 (Right x, Right y) = pure $ Right $ 'List'.intersect x y
94 eval (l *. r) = eval l >>= \x->eval r >>= \y->case (x, y) of
95 (Left x, Left y) = pure $ Left (x * y)
96 (Left x, Right y) = pure $ Right [x*y\\y<-y]
97 (Right x, Left y) = fail "Set *. Elem is illegal"
98 (Right x, Right y) = pure $ Right $ 'List'.intersect x y
99 eval (v =. b) = eval b >>= store v
100
101 instance eval Logical Bool
102 where
103 eval TRUE = pure True
104 eval FALSE = pure False
105 eval (e In s) = liftM2 'List'.elem (iselem (eval e)) (isset (eval s))
106 eval (e1 ==. e2) = liftM2 (===) (eval e1) (eval e2)
107 eval (e1 <=. e2) = evalExpr e1 >>= \x->evalExpr e2 >>= \y->case (x, y) of
108 (Left e1, Left e2) = pure $ e1 < e2
109 (Left e1, Right e2) = pure $ True
110 (Right e1, Left e2) = pure $ False
111 (Right e1, Right e2) = pure $ length e1 < length e2
112 where
113 evalExpr :: (Expression -> Sem Val)
114 evalExpr = eval
115 eval (Not l) = not <$> eval l
116 eval (l1 ||. l2) = liftM2 (||) (eval l1) (eval l2)
117 eval (l1 &&. l2) = liftM2 (&&) (eval l1) (eval l2)
118
119 instance eval Stmt ()
120 where
121 eval (Expression e) = eval e >>| pure ()
122 eval (Logical l) = eval l >>| pure ()
123 eval (For i e s) = (eval e >>= store i) *> eval s
124 eval (If l s1 s2) = eval l >>= \b->if b (eval s1) (eval s2)
125
126 class print t :: t [String] -> [String]
127 instance print Expression
128 where
129 print (New s) c = ["[":'List'.intersperse "," $ map toString s] ++ ["]":c]
130 print (Elem i) c = [toString i:c]
131 print (Variable i) c = [i:c]
132 print (Size s) c = ["size(":print s [")":c]]
133 print (l +. r) c = ["(":print l ["+.":print r [")":c]]]
134 print (l -. r) c = ["(":print l ["-.":print r [")":c]]]
135 print (l *. r) c = ["(":print l ["*.":print r [")":c]]]
136 print (l =. r) c = [l,"=.":print r c]
137
138 instance print Logical
139 where
140 print TRUE c = ["True":c]
141 print FALSE c = ["False":c]
142 print (e In s) c = print e [" in ":print s c]
143 print (e1 ==. e2) c = ["(":print e1 ["==.":print e2 [")":c]]]
144 print (e1 <=. e2) c = ["(":print e1 ["<=.":print e2 [")":c]]]
145 print (Not l) c = ["not (":print l [")":c]]
146 print (l1 ||. l2) c = ["(":print l1 ["||.":print l2 [")":c]]]
147 print (l1 &&. l2) c = ["(":print l1 ["&&.":print l2 [")":c]]]
148
149 instance print Stmt
150 where
151 print (Expression e) c = print e c
152 print (Logical l) c = print l c
153 print (For i e s) c = ["For ",i,"=":print e ["in":print s ["Rof":c]]]
154 print (If l s1 s2) c = ["If":print l ["then":print s1 ["else":print s2 ["Fi":c]]]]
155
156 // === simulation
157 stateShared :: Shared SemState
158 stateShared = sharedStore "sharedSemState" 'Map'.newMap
159
160 derive class iTask Expression, Logical, Stmt
161
162 main :: Task SemState
163 main = 'iTasks'.forever $
164 enterInformation "Enter a statement" []
165 -|| viewSharedInformation "Old state" [ViewAs printer] stateShared
166 >&^ viewSharedInformation "Print" [ViewAs viewer]
167 >&> viewSharedInformation "New state" [ViewAs $ fmap printer] o mapRead evaler o ((>*<) stateShared)
168 >>* [OnAction (Action "Execute") $ ifValue (\e->e=:(Right _)) $ \(Right s)->set s stateShared]
169 where
170 viewer = maybe
171 "No expression selected"
172 ('Text'.join " " o flip print [])
173 evaler :: (SemState, Maybe Stmt) -> Either String SemState
174 evaler (s, t) = maybe
175 (Left "No expression selected")
176 (\e->execStateT (eval e) s) t
177 printer m = [k +++ "=" +++ toSingleLineText v\\(k,v)<-'Map'.toList m]
178
179 Start w = doTasks main w