fix escapes in literal strings
[cc1516.git] / gen.icl
diff --git a/gen.icl b/gen.icl
index a00275d..53a1de7 100644 (file)
--- a/gen.icl
+++ b/gen.icl
@@ -33,30 +33,66 @@ FALSE :== 0
 :: SSMProgram :== [Instr]
 :: GenError = Error String
 :: Addressbook :== 'Map'.Map String Address
-:: Address = LAB String | ADDR Int
+:: Address = LAB String Int | ADDR Int
 :: Gen a :== RWST () SSMProgram (Addressbook, [Label]) (Either GenError) a
 
 labelStream :: [Label]
 labelStream = ["lbl_" +++ toString i\\i<-[1..]]
 
+defaultAddressBook :: Addressbook 
+defaultAddressBook = extend "1printint" (LAB "1printint" 1)
+       $ extend "1printchar" (LAB "1printchar" 1)
+       $ extend "1readchar" (LAB "1readchar" 0)
+       $ extend "1readint" (LAB "1readint" 0)
+       $ extend "isEmpty" (LAB "isempty" 1)
+       'Map'.newMap
+
 gen :: AST -> Either String String
-gen (AST fds) = case evalRWST prog () ('Map'.newMap, labelStream) of
+gen (AST fds) = case evalRWST prog () (defaultAddressBook, labelStream) of
             Left (Error e) = Left e
             Right (_, p) = Right $ toString p
     where
         prog = tell [
                        Instr "bsr" [L "main"] "",
                        Instr "halt" [] ""
-                       ] >>| mapM_ g fds
+                       ] >>| tell programContext
+            >>| mapM_ g fds
 
-//Current issues:
-//All VarDecls are added as function, how to deal with assignments?
-//  (And when we deal with assignments, how to deal with assignments to higher order functions?)
-//Dealing with arguments
-//Dealing with types that do not fit on the Stack
-//  Probably completely change LoadPlace to a Type and a position relative to *something*
-//  And where the type determines if this position is a pointer to the heap or an
-//  unboxed value
+programContext :: SSMProgram
+programContext =    [Lab "1printint"
+                    ,Instr "link" [Lit 0] ""
+                    ,Instr "ldl" [Lit -2] "load first argument"
+                                       ,Instr "trap" [Lit 0] "print int"
+                    ,Instr "unlink" [] ""
+                    ,Instr "ret" [] ""
+                                       ,Lab "1printchar"
+                    ,Instr "link" [Lit 0] ""
+                    ,Instr "ldl" [Lit -2] "load first argument"
+                                       ,Instr "trap" [Lit 1] "print char"
+                    ,Instr "unlink" [] ""
+                    ,Instr "ret" [] ""
+                    ,Lab "1readint"
+                    ,Instr "link" [Lit 0] ""
+                                       ,Instr "trap" [Lit 10] "read int"
+                    ,Instr "str" [Raw "RR"] ""
+                    ,Instr "unlink" [] ""
+                    ,Instr "ret" [] ""
+                    ,Lab "1readchar"
+                    ,Instr "link" [Lit 0] ""
+                                       ,Instr "trap" [Lit 11] "read char"
+                    ,Instr "str" [Raw "RR"] ""
+                    ,Instr "unlink" [] ""
+                    ,Instr "ret" [] ""
+                    ,Lab "isempty"
+                    ,Instr "link" [Lit 0] ""
+                    ,Instr "ldl" [Lit -2] "load prt to list"
+                    ,Instr "lda" [Lit 0] "derefrence ptr"
+                    ,Instr "ldc" [Lit 0] ""
+                    ,Instr "eq" [] "test for null pointer"
+                    ,Instr "str" [Raw "RR"] ""
+                    ,Instr "unlink" [] ""
+                    ,Instr "ret" [] ""
+                    ]
 
 //helper functions for the gen monad
 getAdressbook :: Gen Addressbook
@@ -98,6 +134,12 @@ instance g Op2 where
                    BiOr = "or"
                    BiCons = abort "Shit, Cons, how to deal with this?"
 
+instance g FieldSelector where
+       g FieldFst = tell [Instr "lda" [Lit 0] "fst"]
+       g FieldSnd = tell [Instr "lda" [Lit 1] "snd"]
+       g FieldHd = tell [Instr "lda" [Lit -1] "hd"]
+       g FieldTl = tell [Instr "lda" [Lit 0] "tl"]
+
 instance g Expr where
     g (IntExpr _ i) = tell [Instr "ldc" [Lit i] ""]
     g (CharExpr _ c) = tell [Instr "ldc" [Lit (toInt c)] ""]
@@ -116,19 +158,21 @@ instance g Expr where
                >>| tell [Instr "sth" [] ""]
                >>| tell [Instr "ajs" [Lit -1] ""]
     g (VarExpr _ (VarDef k fs)) = getAdressbook >>= \ab->case 'Map'.get k ab of
-               Nothing = liftT (Left $ Error "PANIC: undefined variable")
-               Just (ADDR t) = tell [Instr "ldl" [Lit t] ""]
-               Just (LAB t) = liftT (Left $ Error "PANIC: variable and function name clash")
-               //load k >>= \instr-> tell [instr] //note: pure is pure for list, i.e. []
-    g (FunExpr _ k es fs) = 
-               mapM g es
-               >>| jump "bsr" k
-               >>| tell [Instr "ldr" [Raw "RR"] ""]
+               Just (ADDR t) = tell [Instr "ldl" [Lit t] ""] >>| mapM_ g fs >>| pure ()
+               _ = liftT (Left $ Error "Higher order functions not implemented")
+    g (FunExpr _ k es fs) = getAdressbook >>= \ab->case 'Map'.get k ab of
+               Just (LAB l arity) = if (arity <> (length es))
+                       (liftT $ Left $ Error "Higher order functions not implemented")
+                       (       mapM_ g es
+                               >>| jump "bsr" k
+                       >>| mapM_ (const $ tell [Instr "ajs" [Lit -1] ""]) es //clean up args
+                               >>| tell [Instr "ldr" [Raw "RR"] ""])
+               _ = liftT (Left $ Error "Funcall to variable?")
 
 jump :: String String -> Gen ()
 jump instr k = getAdressbook >>= \ab->case 'Map'.get k ab of
        Nothing = liftT (Left $ Error $ concat ["PANIC: ", k, " not found as function"])
-       Just (LAB t) = tell [Instr instr [L t] (k +++"()")]
+       Just (LAB t _) = tell [Instr instr [L t] (k +++"()")]
        Just (ADDR t) = liftT (Left $ Error $ "PANIC: jump should go to label")
 
 instance g Stmt where
@@ -154,9 +198,13 @@ instance g Stmt where
     g (AssStmt (VarDef k fs) e) = 
         g e >>| getAdressbook >>= \ab->case 'Map'.get k ab of
             Nothing = liftT (Left $ Error $ concat ["PANIC: ", k, " not found as var"])
-            Just (LAB t) = liftT (Left $ Error $ "PANIC: cannot assign to function")
+            Just (LAB t _) = liftT (Left $ Error $ "PANIC: cannot assign to function")
             Just (ADDR t) = tell [Instr "stl" [Lit t] ""]
-    g (FunStmt k es) = mapM g es >>| jump "bsr" k
+    g (FunStmt k es fs) = mapM_ g es 
+        >>| jump "bsr" k
+        >>| mapM_ (const $ tell [Instr "ajs" [Lit -1] ""]) es //clean up args
+        >>| mapM_ g fs
+               >>| pure ()
     g (ReturnStmt Nothing) = tell [Instr "unlink" [] ""]
                >>| tell [Instr "ret" [] ""]
     g (ReturnStmt (Just e)) = g e
@@ -165,6 +213,7 @@ instance g Stmt where
 
 foldVarDecl :: Int VarDecl -> Gen Int
 foldVarDecl x (VarDecl _ _ k e) = g e 
+    >>| annote x k
        >>| updateAdressbook (extend k (ADDR x)) >>| pure (x + 1)
 
 addVars :: [String] -> (Addressbook -> Addressbook)
@@ -174,17 +223,21 @@ addVars [x:xs] = \ab->extend x (ADDR (-2 - (length xs))) (addVars xs ab)
 instance g FunDecl where
     g (FunDecl _ k args _ vds stms) = 
         //varDecls can call the enclosing function, so first reserve a label for it 
-        updateAdressbook (extend k (LAB k)) >>|
+        updateAdressbook (extend k (LAB k (length args))) >>|
         getAdressbook >>= \oldMap ->
                updateAdressbook (addVars args) >>|
         tell [Lab k] >>|
                tell [Instr "link" [Lit 0] ""] >>|
-        //then generate functions for the VarDecls
+        //add the vars
         foldM foldVarDecl 1 vds  >>|
-        //then the main function 
+        //and the statements
         mapM_ g stms >>|
         updateAdressbook (const oldMap) >>| pure ()
 
+annote :: Int String -> Gen ()
+annote pos key = 
+    tell [Instr "annote" [Raw "MP", Lit pos, Lit pos, Raw "green", Raw key] ""]
+
 class print a :: a -> [String]
 
 instance print Instr where