Fixed printing from lambdas
[cc1516.git] / gen.icl
1 implementation module gen
2
3 import StdMisc
4 import StdList
5 import StdOverloaded
6 import StdString
7 from StdFunc import id, const
8 import StdTuple
9 import StdEnum
10
11 import Data.Func
12 import qualified Data.Map as Map
13 import Data.List
14 import Data.Either
15 import Data.Tuple
16 import Data.Functor
17 import Data.Monoid
18 import Data.Maybe
19 import Control.Applicative
20 import Control.Monad
21 import Control.Monad.Trans
22 from Text import class Text(concat), instance Text String
23
24 import AST
25 import RWST
26
27 TRUE :== -1
28 FALSE :== 0
29 :: Instr = Instr String [Arg] String
30 | Lab Label
31 :: Label :== String
32 :: Arg = L Label | Lit Int | Raw String
33 :: SSMProgram :== [Instr]
34 :: GenError = Error String
35 :: Addressbook :== 'Map'.Map String Address
36 :: Address = LAB String Int Int | ADDR Int Int
37 :: Gen a :== RWST () SSMProgram (Addressbook, [Label]) (Either GenError) a
38
39 labelStream :: [Label]
40 labelStream = ["lbl_" +++ toString i\\i<-[1..]]
41
42 defaultAddressBook :: [FunDecl] -> Addressbook
43 defaultAddressBook fd = extend "1printint" (LAB "1printint" 1 0)
44 $ extend "1printchar" (LAB "1printchar" 1 1)
45 $ extend "read" (LAB "read" 0 2)
46 $ extend "1readint" (LAB "1readint" 0 3)
47 $ extend "isEmpty" (LAB "isempty" 1 4)
48 $ addFuncs fd 5
49 where
50 addFuncs [] _ = 'Map'.newMap
51 addFuncs [(FunDecl _ k args _ _ _):xs] n =
52 extend k (LAB k (length args) n) $ addFuncs xs (n+1)
53
54 gen :: AST -> Either String String
55 gen (AST fds) = case evalRWST prog () (defaultAddressBook fds, labelStream) of
56 Left (Error e) = Left e
57 Right (_, p) = Right $ toString p
58 where
59 prog = tell [
60 Instr "bsr" [L "main"] "",
61 Instr "halt" [] ""
62 ] >>| tell (programContext fds)
63 >>| mapM_ g fds
64
65 programContext :: [FunDecl] -> SSMProgram
66 programContext x = [Lab "1func"
67 :fS ["1printint" ,"1printchar"
68 ,"read" ,"1readint"
69 ,"isEmpty":map (\(FunDecl _ k _ _ _ _)->k) x] 0] ++ context
70 where
71
72 fS :: [String] Int -> SSMProgram
73 fS [] _ = []
74 fS [k:xs] n = [
75 Lab $ "1next" +++ toString n
76 ,Instr "ldr" [Raw "R5"] ""
77 ,Instr "ldc" [Lit n] $ "branch to: " +++ k
78 ,Instr "eq" [] ""
79 ,Instr "brf" [L $ "1next" +++ (toString $ n + 1)] ""
80 ,Instr "bra" [L k] ""
81 :fS xs $ n+1]
82 context :: SSMProgram
83 context = [Lab "1printint"
84 ,Instr "link" [Lit 0] ""
85 ,Instr "ldl" [Lit -2] "load first argument"
86 ,Instr "trap" [Lit 0] "print int"
87 ,Instr "unlink" [] ""
88 ,Instr "ret" [] ""
89 ,Lab "1printchar"
90 ,Instr "link" [Lit 0] ""
91 ,Instr "ldl" [Lit -2] "load first argument"
92 ,Instr "trap" [Lit 1] "print char"
93 ,Instr "unlink" [] ""
94 ,Instr "ret" [] ""
95 ,Lab "read"
96 ,Instr "link" [Lit 0] ""
97 ,Instr "trap" [Lit 11] "read char"
98 ,Instr "str" [Raw "RR"] ""
99 ,Instr "unlink" [] ""
100 ,Instr "ret" [] ""
101 ,Lab "isempty"
102 ,Instr "link" [Lit 0] ""
103 ,Instr "ldl" [Lit -2] "load prt to list"
104 ,Instr "lda" [Lit 0] "derefrence ptr"
105 ,Instr "ldc" [Lit 0] ""
106 ,Instr "eq" [] "test for null pointer"
107 ,Instr "str" [Raw "RR"] ""
108 ,Instr "unlink" [] ""
109 ,Instr "ret" [] ""
110 ,Lab "read"
111 ]
112
113 getAdressbook :: Gen Addressbook
114 getAdressbook = gets fst
115
116 updateAdressbook :: (Addressbook -> Addressbook) -> Gen Addressbook
117 updateAdressbook f = modify (appFst f) >>| getAdressbook
118
119 extend :: String Address Addressbook -> Addressbook
120 extend k pl g = 'Map'.put k pl g
121
122 fresh :: Gen Label
123 fresh = gets snd >>= \vars->
124 modify (appSnd $ const $ tail vars) >>|
125 pure (head vars)
126
127 class g a :: a -> Gen ()
128
129 instance g Op1 where
130 g UnNegation = tell [Instr "not" [] ""]
131 g UnMinus = tell [Instr "neg" [] ""]
132
133 instance g Op2 where
134 g o = tell [Instr s [] ""]
135 where
136 s = case o of
137 BiPlus = "add"
138 BiMinus = "sub"
139 BiTimes = "mul"
140 BiDivide = "div"
141 BiMod = "mod"
142 BiEquals = "eq"
143 BiLesser = "lt"
144 BiGreater = "gt"
145 BiLesserEq = "le"
146 BiGreaterEq = "ge"
147 BiUnEqual = "ne"
148 BiAnd = "and"
149 BiOr = "or"
150 BiCons = abort "Shit, Cons, how to deal with this?"
151
152 instance g FieldSelector where
153 g FieldFst = tell [Instr "lda" [Lit -1] "fst"]
154 g FieldSnd = tell [Instr "lda" [Lit 0] "snd"]
155 g FieldHd = tell [Instr "lda" [Lit -1] "hd"]
156 g FieldTl = tell [Instr "lda" [Lit 0] "tl"]
157
158 instance g Expr where
159 g (IntExpr _ i) = tell [Instr "ldc" [Lit i] ""]
160 g (CharExpr _ c) = tell [Instr "ldc" [Lit (toInt c)] ""]
161 g (BoolExpr _ b) = tell [Instr "ldc" [Lit (if b TRUE FALSE)] ""]
162 g (EmptyListExpr _) = tell [Instr "ldc" [Lit 0] ""]
163 >>| tell [Instr "sth" [] ""]
164 g (Op1Expr _ o e) = g e >>| g o
165 g (Op2Expr _ e1 BiCons e2) = g e2 >>| g e1
166 >>| tell [Instr "sth" [] ""]
167 >>| tell [Instr "ajs" [Lit -1] ""]
168 >>| tell [Instr "sth" [] ""]
169 g (Op2Expr _ e1 op e2) = g e1 >>| g e2 >>| g op
170 g (TupleExpr _ (e1,e2)) = g e1
171 >>| g e2
172 >>| tell [Instr "stmh" [Lit 2] ""]
173 g (VarExpr _ (VarDef k fs)) = getAdressbook >>= \ab->case 'Map'.get k ab of
174 Just (ADDR t arity) = tell [Instr "ldl" [Lit t] ""] >>| mapM_ g fs >>| pure ()
175 Just (LAB l _ fn) = tell
176 [Instr "ldc" [Lit fn] ""
177 ,Instr "sth" [] ""
178 ,Instr "ldc" [Lit 0] ""
179 ,Instr "sth" [] ""
180 ,Instr "ajs" [Lit -1] ""]
181 g (LambdaExpr _ _ _) = liftT $ Left $ Error "PANIC: Lambdas should be unfolded"
182 g (FunExpr _ k es fs) = funnyStuff k es fs
183
184 funnyStuff :: String [Expr] [FieldSelector] -> Gen ()
185 funnyStuff k es fs = getAdressbook >>= \ab->case 'Map'.get k ab of
186 //Identifier points to function
187 Just (LAB l arity fn) = if (arity <> (length es))
188 //Function is not complete
189 ( tell
190 [Instr "ldc" [Lit fn] "Store function number"
191 ,Instr "sth" [] ""
192 ,Instr "ldc" [Lit $ length es] "Store arity"
193 ,Instr "sth" [] ""
194 ,Instr "ajs" [Lit -1] ""]
195 >>| mapM_ g es
196 >>| if (isEmpty es) (pure ()) (tell
197 [Instr "stmh" [Lit $ length es] "Store arguments"
198 ,Instr "ajs" [Lit -1] ""]))
199 //Function is complete
200 ( mapM_ g es
201 >>| getAdressbook >>= \ab->(case 'Map'.get k ab of
202 Nothing = liftT (Left $ Error $ concat ["PANIC: ", k, " not found as function"])
203 Just (LAB t _ _) = tell [Instr "bsr" [L t] (k +++"()")]
204 Just (ADDR t arity) = liftT (Left $ Error "NO ADDRESS JUMPING FFS")
205 )
206 >>| tell
207 [Instr "ajs" [Lit $ ~(length es)] "Clean arguments"
208 ,Instr "ldr" [Raw "RR"] ""])
209 //Identifier points to variable, thus higher order function
210 Just (ADDR t arity) = if (arity <> (length es))
211 //Function is still not complete
212 ( fresh >>= \finish->fresh >>= \start->tell [
213 //Store function number
214 Instr "ldl" [Lit t] "STARTING HIGHER ORDER UPDATE"
215 ,Instr "ldh" [Lit 0] "get function number"
216 ,Instr "sth" [] "Store"
217 //Store function arity
218 ,Instr "ldl" [Lit t] "get pointer again"
219 ,Instr "ldh" [Lit 1] "get function arity"
220 ,Instr "ldc" [Lit $ length es] "add argument number"
221 ,Instr "add" [] "add"
222 ,Instr "sth" [] "Store"
223 ,Instr "ajs" [Lit -1] "Adjust pointer"
224 //load the arguments
225 ,Instr "ldl" [Lit t] ""
226 ,Instr "ldh" [Lit 1] "Load available arguments"
227 ,Instr "str" [Raw "R5"] "Store available args in register"
228 ,Instr "ldc" [Lit 0] "Store offset"
229 ,Instr "str" [Raw "R6"] "Store offset in register"
230 ,Lab start
231 ,Instr "ldr" [Raw "R5"] ""
232 ,Instr "ldc" [Lit 0] ""
233 ,Instr "eq" [] ""
234 ,Instr "brt" [L finish] "Done pushing arg, bye"
235 //Load heapadress
236 ,Instr "ldl" [Lit t] ""
237 ,Instr "ldr" [Raw "R6"] ""
238 ,Instr "add" [] "Corrected heapaddress"
239 ,Instr "ldh" [Lit 2] "Load argument"
240 ,Instr "sth" [] "And store it immediatly after"
241 //Decrease available arguments
242 ,Instr "ldr" [Raw "R5"] ""
243 ,Instr "ldc" [Lit 1] ""
244 ,Instr "sub" [] ""
245 ,Instr "str" [Raw "R5"] ""
246 //Increase available arguments
247 ,Instr "ldr" [Raw "R6"] ""
248 ,Instr "ldc" [Lit 1] ""
249 ,Instr "add" [] ""
250 ,Instr "str" [Raw "R6"] ""
251 ,Instr "bra" [L start] ""
252 ,Lab finish
253 ]
254 >>| mapM_ g es
255 >>| tell
256 [Instr "stmh" [Lit $ length es] "Store extra args"
257 ,Instr "ajs" [Lit -1] ""]
258 )
259 //Function is complete
260 ( fresh >>= \finish->fresh >>= \start->tell [
261 Instr "ldl" [Lit t] "STARTING HIGHER ORDER CALL"
262 ,Instr "ldh" [Lit 1] "Load available arguments"
263 ,Instr "str" [Raw "R5"] "Store available args in register"
264 ,Instr "ldc" [Lit 0] "Store offset"
265 ,Instr "str" [Raw "R6"] "Store offset in register"
266
267 ,Lab start
268 ,Instr "ldr" [Raw "R5"] ""
269 ,Instr "ldc" [Lit 0] ""
270 ,Instr "eq" [] ""
271 ,Instr "brt" [L finish] "Done pushing arg, bye"
272 //Load heapadress
273 ,Instr "ldl" [Lit t] ""
274 ,Instr "ldr" [Raw "R6"] ""
275 ,Instr "add" [] "Corrected heapaddress"
276 ,Instr "ldh" [Lit 2] "Load argument"
277 //Decrease available arguments
278 ,Instr "ldr" [Raw "R5"] ""
279 ,Instr "ldc" [Lit 1] ""
280 ,Instr "sub" [] ""
281 ,Instr "str" [Raw "R5"] ""
282 //Increase available arguments
283 ,Instr "ldr" [Raw "R6"] ""
284 ,Instr "ldc" [Lit 1] ""
285 ,Instr "add" [] ""
286 ,Instr "str" [Raw "R6"] ""
287 ,Instr "bra" [L start] ""
288 ,Lab finish
289 ]
290 >>| mapM_ g es
291 >>| tell
292 [Instr "ldl" [Lit t] ""
293 ,Instr "ldh" [Lit 0] "Get function number"
294 ,Instr "str" [Raw "R5"] ""
295 ,Instr "bsr" [L "1func"] "HIGHER ORDER END"
296 ,Instr "ldl" [Lit t] ""
297 ,Instr "ldh" [Lit 1] ""
298 ,Instr "neg" [] ""
299 ,Instr "ldr" [Raw "SP"] ""
300 ,Instr "add" [] ""
301 ,Instr "ldc" [Lit $ length es + 1] ""
302 ,Instr "sub" [] ""
303 ,Instr "str" [Raw "SP"] ""
304 ,Instr "ldr" [Raw "RR"] ""
305 ]
306 )
307 Nothing = liftT (Left $ Error $ "PANIC: Undefined function: " +++ k)
308
309 instance g Stmt where
310 g (IfStmt cond th el) =
311 fresh >>= \elseLabel->
312 fresh >>= \endLabel->
313 g cond >>|
314 tell [Instr "brf" [L elseLabel] "branch else"] >>|
315 mapM_ g th >>|
316 tell [Instr "bra" [L endLabel] "branch end if"] >>|
317 tell [Lab elseLabel] >>|
318 mapM_ g el >>|
319 tell [Lab endLabel]
320 g (WhileStmt cond th) =
321 fresh >>= \startLabel->
322 fresh >>= \endLabel ->
323 tell [Lab startLabel] >>|
324 g cond >>|
325 tell [Instr "brf" [L endLabel] "branch end while"] >>|
326 mapM_ g th >>|
327 tell [Instr "bra" [L startLabel] "branch start while"] >>|
328 tell [Lab endLabel]
329 g (AssStmt (VarDef k fs) e) =
330 g e >>| getAdressbook >>= \ab->case 'Map'.get k ab of
331 Nothing = liftT (Left $ Error $ concat ["PANIC: ", k, " not found as var"])
332 Just (LAB t _ _) = liftT (Left $ Error $ "PANIC: cannot assign to function")
333 Just (ADDR t ar) = tell [Instr "stl" [Lit t] ""]
334 g (FunStmt k es fs) = funnyStuff k es fs
335 g (ReturnStmt Nothing) = tell [Instr "unlink" [] ""]
336 >>| tell [Instr "ret" [] ""]
337 g (ReturnStmt (Just e)) = g e
338 >>| tell [Instr "str" [Raw "RR"] ""]
339 >>| g (ReturnStmt Nothing)
340
341 foldVarDecl :: Int VarDecl -> Gen Int
342 foldVarDecl x (VarDecl _ mt k e) = g e
343 >>| annote x k
344 >>| updateAdressbook (extend k (ADDR x $ arity $ fromJust mt))
345 >>| pure (x + 1)
346
347 arity :: Type -> Int
348 arity (_ ->> x) = 1 + arity x
349 arity _ = 0
350
351 addVars :: Type [String] -> (Addressbook -> Addressbook)
352 addVars _ [] = id
353 addVars (t ->> ts) [x:xs] = \ab->
354 extend x (ADDR (-2 - (length xs)) (arity t)) (addVars ts xs ab)
355 addVars t [x] = \ab->
356 extend x (ADDR -2 0) ab
357
358 instance g FunDecl where
359 g (FunDecl _ k args mt vds stms) =
360 //varDecls can call the enclosing function, so first reserve a label for it
361 getAdressbook >>= \oldMap ->
362 updateAdressbook (addVars (fromJust mt) args) >>|
363 tell [Lab k] >>|
364 tell [Instr "link" [Lit 0] ""] >>|
365 //add the vars
366 foldM foldVarDecl 1 vds >>|
367 //and the statements
368 mapM_ g stms >>|
369 //Ugly hack to always return
370 g (ReturnStmt Nothing) >>|
371 updateAdressbook (const oldMap) >>| pure ()
372
373 annote :: Int String -> Gen ()
374 annote pos key =
375 tell [Instr "annote" [Raw "MP", Lit pos, Lit pos, Raw "black", Raw key] ""]
376
377 class print a :: a -> [String]
378
379 instance print Instr where
380 print (Lab l) = [l, ":", "\n"]
381 print (Instr i args com) = ["\t", i] ++ print args ++ [" ;", com, "\n"]
382
383 instance print [Arg] where
384 print args = (map toString args)
385
386 instance toString Arg where
387 toString (L l) = l
388 toString (Lit int) = toString int
389 toString (Raw s) = s
390
391 instance toString SSMProgram where
392 toString p = concat $ intersperse " " $ map (\i-> concat $ intersperse " " $ print i) p