HIGHER ORDER FUNCTIONSgit add .git add .!
[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 g (FunExpr _ k es fs) = getAdressbook >>= \ab->case 'Map'.get k ab of
181 //Identifier points to function
182 Just (LAB l arity fn) = if (arity <> (length es))
183 ( tell
184 [Instr "ldc" [Lit fn] "Store function number"
185 ,Instr "sth" [] ""
186 ,Instr "ldc" [Lit $ length es] "Store arity"
187 ,Instr "sth" [] ""
188 ,Instr "ajs" [Lit -1] ""]
189 >>| mapM_ g es
190 >>| if (isEmpty es) (pure ()) (tell
191 [Instr "stmh" [Lit $ length es] "Store arguments"
192 ,Instr "ajs" [Lit -1] ""]))
193 ( mapM_ g es
194 >>| jump "bsr" k
195 >>| tell
196 [Instr "ajs" [Lit $ ~(length es)] "Clean arguments"
197 ,Instr "ldr" [Raw "RR"] ""])
198 //Identifier points to variable, thus higher order function
199 Just (ADDR t arity) = if (arity <> (length es))
200 ( fresh >>= \finish->
201 fresh >>= \start->
202 tell
203 [Instr "ldl" [Lit t] ""
204 ,Instr "ldma" [Lit 0, Lit 2] "Load funcall and arity"
205 ,Instr "ldc" [Lit $ length es] "Push extra arity on stack"
206 ,Instr "add" [] "Increase arity"
207 ,Instr "ldl" [Lit t] ""
208 ,Instr "ldh" [Lit 1] "Load available arguments"
209 ,Instr "str" [Raw "R5"] "Save available arguments"
210 ,Lab start
211 ,Instr "ldr" [Raw "R5"] "Load available arguments"
212 ,Instr "ldc" [Lit 0] ""
213 ,Instr "eq" [] ""
214 ,Instr "brt" [L finish] ""
215 ,Instr "ldc" [Lit 1] "Decrement available arguments"
216 ,Instr "sub" [] ""
217 ,Instr "str" [Raw "R5"] "Push available arguments"
218 ,Instr "bra" [L start] ""
219 ,Lab finish
220 ]
221 >>| mapM_ g es )
222 ( fresh >>= \finish->
223 fresh >>= \start->
224 tell
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
231 ,Lab start
232 ,Instr "ldr" [Raw "R5"] ""
233 ,Instr "ldc" [Lit 0] ""
234 ,Instr "eq" [] ""
235 ,Instr "brt" [L finish] "Done pushing arg, bye"
236 //Load heapadress
237 ,Instr "ldl" [Lit t] ""
238 ,Instr "ldr" [Raw "R6"] ""
239 ,Instr "add" [] "Corrected heapaddress"
240 ,Instr "ldh" [Lit 2] "Load argument"
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 "ldl" [Lit t] ""
257 ,Instr "ldh" [Lit 0] "Get function number"
258 ,Instr "str" [Raw "R5"] ""
259 ,Instr "bsr" [L "1func"] ""
260 ,Instr "ldr" [Raw "MP"] ""
261 ,Instr "ldc" [Lit t] ""
262 ,Instr "add" [] ""
263 ,Instr "str" [Raw "SP"] ""
264 ,Instr "ldr" [Raw "RR"] ""
265 ]
266 )
267 Nothing = liftT (Left $ Error "Undefined function!!!")
268
269 jump :: String String -> Gen ()
270 jump instr k = getAdressbook >>= \ab->case 'Map'.get k ab of
271 Nothing = liftT (Left $ Error $ concat ["PANIC: ", k, " not found as function"])
272 Just (LAB t _ _) = tell [Instr instr [L t] (k +++"()")]
273 Just (ADDR t arity) = liftT (Left $ Error "Address as jump???")
274
275 instance g Stmt where
276 g (IfStmt cond th el) =
277 fresh >>= \elseLabel->
278 fresh >>= \endLabel->
279 g cond >>|
280 tell [Instr "brf" [L elseLabel] "branch else"] >>|
281 mapM_ g th >>|
282 tell [Instr "bra" [L endLabel] "branch end if"] >>|
283 tell [Lab elseLabel] >>|
284 mapM_ g el >>|
285 tell [Lab endLabel]
286 g (WhileStmt cond th) =
287 fresh >>= \startLabel->
288 fresh >>= \endLabel ->
289 tell [Lab startLabel] >>|
290 g cond >>|
291 tell [Instr "brf" [L endLabel] "branch end while"] >>|
292 mapM_ g th >>|
293 tell [Instr "bra" [L startLabel] "branch start while"] >>|
294 tell [Lab endLabel]
295 g (AssStmt (VarDef k fs) e) =
296 g e >>| getAdressbook >>= \ab->case 'Map'.get k ab of
297 Nothing = liftT (Left $ Error $ concat ["PANIC: ", k, " not found as var"])
298 Just (LAB t _ _) = liftT (Left $ Error $ "PANIC: cannot assign to function")
299 Just (ADDR t ar) = tell [Instr "stl" [Lit t] ""]
300 g (FunStmt k es fs) = mapM_ g es
301 >>| jump "bsr" k
302 >>| tell [Instr "ajs" [Lit (~(length es))] ""] //clean up args
303 >>| mapM_ g fs
304 >>| pure ()
305 g (ReturnStmt Nothing) = tell [Instr "unlink" [] ""]
306 >>| tell [Instr "ret" [] ""]
307 g (ReturnStmt (Just e)) = g e
308 >>| tell [Instr "str" [Raw "RR"] ""]
309 >>| g (ReturnStmt Nothing)
310
311 foldVarDecl :: Int VarDecl -> Gen Int
312 foldVarDecl x (VarDecl _ mt k e) = g e
313 >>| annote x k
314 >>| updateAdressbook (extend k (ADDR x $ arity $ fromJust mt))
315 >>| pure (x + 1)
316
317 arity :: Type -> Int
318 arity (_ ->> x) = 1 + arity x
319 arity _ = 0
320
321 addVars :: Type [String] -> (Addressbook -> Addressbook)
322 addVars _ [] = id
323 addVars (t ->> ts) [x:xs] = \ab->
324 extend x (ADDR (-2 - (length xs)) (arity t)) (addVars ts xs ab)
325 addVars t [x] = \ab->
326 extend x (ADDR -2 0) ab
327
328 instance g FunDecl where
329 g (FunDecl _ k args mt vds stms) =
330 //varDecls can call the enclosing function, so first reserve a label for it
331 getAdressbook >>= \oldMap ->
332 updateAdressbook (addVars (fromJust mt) args) >>|
333 tell [Lab k] >>|
334 tell [Instr "link" [Lit 0] ""] >>|
335 //add the vars
336 foldM foldVarDecl 1 vds >>|
337 //and the statements
338 mapM_ g stms >>|
339 //Ugly hack to always return
340 g (ReturnStmt Nothing) >>|
341 updateAdressbook (const oldMap) >>| pure ()
342
343 annote :: Int String -> Gen ()
344 annote pos key =
345 tell [Instr "annote" [Raw "MP", Lit pos, Lit pos, Raw "green", Raw key] ""]
346
347 class print a :: a -> [String]
348
349 instance print Instr where
350 print (Lab l) = [l, ":", "\n"]
351 print (Instr i args com) = ["\t", i] ++ print args ++ [" ;", com, "\n"]
352
353 instance print [Arg] where
354 print args = (map toString args)
355
356 instance toString Arg where
357 toString (L l) = l
358 toString (Lit int) = toString int
359 toString (Raw s) = s
360
361 instance toString SSMProgram where
362 toString p = concat $ intersperse " " $ map (\i-> concat $ intersperse " " $ print i) p