0344721385c5334a9bcb335a102ec25369bd3b10
[clean-tests.git] / afp / a11 / a10.icl
1 module a10
2
3 import StdEnv
4
5 import Data.Functor
6 import Control.Applicative
7 import Control.Monad => qualified join
8 import Control.Monad.Trans
9 import Control.Monad.State
10 import Data.Maybe
11 import Data.Error
12 import Data.Either
13 import Data.Func
14 import Text
15
16 :: Step pre post = Step
17 :: High = High
18 :: Low = Low
19
20 class action v
21 where
22 moveToShip :: v (Step High High)
23 moveToQuay :: v (Step High High)
24 moveUp :: v (Step Low High)
25 moveDown :: v (Step High Low)
26 lock :: v (Step Low Low)
27 unlock :: v (Step Low Low)
28 wait :: v (Step a a)
29 (:.) infixl 1 :: (v (Step a b)) (v (Step b c)) -> v (Step a c)
30 While :: (v Bool) (v (Step a a)) -> v (Step a a)
31
32 class expr v
33 where
34 containersBelow :: v Int
35 lit :: t -> v t | toString t
36 (<.) infix 4 :: (v t) (v t) -> (v Bool) | Ord t
37 (>.) infix 4 :: (v t) (v t) -> (v Bool) | Ord t
38 (+.) infix 4 :: (v t) (v t) -> (v t) | + t
39
40 :: Var a = Var Int
41 class var v
42 where
43 def :: (v t) ((v (Var t)) -> (v (Step a b))) -> v (Step a b) | TC t
44 var :: (v (Var t)) -> v t | TC t
45 (=.) infixr 2 :: (v (Var t)) (v t) -> v (Step a a) | TC t
46
47 //Printing
48 :: Printer a = P (Int Int [String] -> [String])
49 runPrinter (P a) = a 0 0
50
51 word :: String -> Printer a
52 word s = P \v i c->[createArray i '\t',s:c]
53
54 instance action Printer
55 where
56 moveToShip = word "moveToShip"
57 moveToQuay = word "moveToQuay"
58 moveUp = word "moveUp"
59 moveDown = word "moveDown"
60 lock = word "lock"
61 unlock = word "unlock"
62 wait = word "wait"
63 (:.) (P a) (P b) = P \v i c->a v i [":.\n":b v i c]
64 While (P b) (P a) = P \v i c->["while (":b v 0 [")\n":a v (i+1) ["\n)":c]]]
65
66 instance expr Printer
67 where
68 containersBelow = P \v i c->["containerBelow":c]
69 lit x = P \v i c->[toString x:c]
70 (<.) (P x) (P y) = P \v i c->x v i [" < ":y v i c]
71 (>.) (P x) (P y) = P \v i c->x v i [" > ":y v i c]
72 (+.) (P x) (P y) = P \v i c->x v i [" + ":y v i c]
73
74 varname i = "v" +++ toString i
75 instance var Printer
76 where
77 def (P e) fun = P \v i c->[createArray i '\t',"def ":e v i [" \\",varname v,".\n":let (P f) = fun (P \_ i c->[varname v:c]) in f (inc v) i c]]
78 var (P e) = P e
79 (=.) (P a) (P b) = P \v i c->[createArray i '\t':a v i [" = ":b v i c]]
80
81 //Evaluating
82 :: Eval a :== StateT SemState (Either String) a
83 cast f = f >>| pure Step
84 fail s = liftT (Left s)
85 runEval = runStateT
86 instance action (StateT SemState (Either String))
87 where
88 moveToShip = cast $ modify (\s->{s & craneOnQuay=False})
89 moveToQuay = cast $ modify (\s->{s & craneOnQuay=True})
90 moveUp = cast $ modify (\s->{s & craneUp=True})
91 moveDown = cast $ modify (\s->{s & craneUp=False})
92 lock = cast $ getState >>= \s->case s of
93 {locked=Just _} = fail "Already locked"
94 {craneOnQuay=True,onQuay=[]} = fail "No container to lock to"
95 {craneOnQuay=False,onShip=[]} = fail "No container to lock to"
96 {craneOnQuay=True,onQuay=[x:xs]} = put {s & onQuay=xs,locked=Just x}
97 {craneOnQuay=False,onShip=[x:xs]} = put {s & onShip=xs,locked=Just x}
98 _ = fail "Shouldn't happen"
99 unlock = cast $ getState >>= \s->case s of
100 {locked=Nothing} = fail "Already unlocked"
101 {craneOnQuay=True,locked=Just x} = put {s & onQuay=[x:s.onQuay],locked=Nothing}
102 {craneOnQuay=False,locked=Just x} = put {s & onShip=[x:s.onShip],locked=Nothing}
103 _ = fail "Shouldn't happen"
104 wait = pure Step
105 (:.) x y = cast $ x >>| y
106 While x y = x >>= \b->if b (y :. (While x y)) (pure Step)
107
108 instance expr (StateT SemState (Either String))
109 where
110 containersBelow = gets (\s->length if s.craneOnQuay s.onQuay s.onShip)
111 lit x = pure x
112 (<.) x y = (<) <$> x <*> y
113 (>.) x y = (>) <$> x <*> y
114 (+.) x y = (+) <$> x <*> y
115
116 instance var (StateT SemState (Either String))
117 where
118 def d fun = d >>= \v->gets (\s->length s.variables) >>= \i->modify (\s->{s & variables=s.variables ++ [dynamic v]}) >>| fun (pure (Var i))
119 var a = a >>= \(Var i)->gets (\s->s.variables !! i) >>= cast
120 where
121 cast :: Dynamic -> StateT SemState (Either String) a | TC a
122 cast (a :: a^) = pure a
123 cast_ = fail "Something went horribly wrong"
124 (=.) a b = cast $ a >>= \(Var i)->b >>= \v->modify (\s->{s & variables=updateAt i (dynamic v) s.variables})
125
126 :: SemState =
127 { onShip :: [String]
128 , onQuay :: [String]
129 , craneUp :: Bool
130 , craneOnQuay :: Bool
131 , locked :: Maybe String
132 , variables :: [Dynamic]
133 }
134
135 state0 =
136 { onShip = []
137 , onQuay = ["apples","beer","camera's"]
138 , craneUp = True
139 , craneOnQuay = True
140 , locked = Nothing
141 , variables = []
142 }
143
144 Start :: (String, Either String SemState, String, Either String SemState)
145 Start =
146 ( concat $ runPrinter loadShip []
147 , execStateT loadShip state0
148 , concat $ runPrinter loadShip2 []
149 , execStateT loadShip2 state0
150 )
151
152 loadShip =
153 While (containersBelow >. lit 0) (
154 moveDown:.
155 lock:.
156 moveUp:.
157 moveToShip:.
158 wait:.
159 moveDown:.
160 wait:.
161 unlock:.
162 moveUp:.
163 moveToQuay
164 )
165
166 loadShip2 =
167 def containersBelow \n.
168 def (lit 0) \m.
169 While (var n >. lit 0) (
170 moveDown:.
171 lock:.
172 moveUp:.
173 moveToShip:.
174 wait:.
175 moveDown:.
176 wait:.
177 unlock:.
178 moveUp:.
179 moveToQuay:.
180 n =. var n +. lit (-1)
181 )