Added default functions, isEmpty does not typecheck...
[cc1516.git] / gen.icl
diff --git a/gen.icl b/gen.icl
index 30bc819..d139804 100644 (file)
--- a/gen.icl
+++ b/gen.icl
@@ -39,24 +39,45 @@ FALSE :== 0
 labelStream :: [Label]
 labelStream = ["lbl_" +++ toString i\\i<-[1..]]
 
+defaultAddressBook :: Addressbook 
+defaultAddressBook = extend "print" (LAB "print")
+                        $ extend "read" (LAB "read")
+                        $ extend "isEmpty" (LAB "isEmpty")
+                        '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
-
-//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
+                       ] >>| tell programContext
+            >>| mapM_ g fds
+
+programContext :: SSMProgram
+programContext =    [Lab "print" //there is no actual IO in SSM
+                    ,Instr "link" [Lit 0] ""
+                    ,Instr "unlink" [] ""
+                    ,Instr "ret" [] ""
+                    ,Lab "read" //there is no actual IO in SSM
+                    ,Instr "link" [Lit 0] ""
+                    ,Instr "ldc" [Lit 0] ""
+                    ,Instr "sth" [] ""
+                    ,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
@@ -74,7 +95,7 @@ fresh = gets snd >>= \vars->
         pure (head vars)
 
 class g a :: a -> Gen ()
-//
+
 instance g Op1 where
        g UnNegation = tell [Instr "not" [] ""]
        g UnMinus = tell [Instr "neg" [] ""]
@@ -121,9 +142,9 @@ instance g Expr where
                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) = 
-//             tell [Instr "ldr" [Raw "MP"] ("old frame pointer")]
-               mapM g es
+               mapM_ g es
                >>| jump "bsr" k
+        >>| mapM_ (const $ tell [Instr "ajs" [Lit -1] ""]) es //clean up args
                >>| tell [Instr "ldr" [Raw "RR"] ""]
 
 jump :: String String -> Gen ()
@@ -133,30 +154,34 @@ jump instr k = getAdressbook >>= \ab->case 'Map'.get k ab of
        Just (ADDR t) = liftT (Left $ Error $ "PANIC: jump should go to label")
 
 instance g Stmt where
-//    g (IfStmt cond th el) = 
-//        fresh >>= \elseLabel->
-//        fresh >>= \endLabel->
-//        g cond >>|
-//        tell [Instr "brf" [L elseLabel] "branch else"] >>|
-//        mapM_ g th >>|
-//        tell [Instr "bra" [L endLabel] "branch end if"] >>|
-//        tell [Lab elseLabel] >>|
-//        mapM_ g el  >>|
-//        tell [Lab endLabel]
-//    g (WhileStmt cond th) = 
-//        fresh >>= \startLabel->
-//        fresh >>= \endLabel ->
-//        tell [Lab startLabel] >>|
-//        g cond >>|
-//        tell [Instr "brf" [L endLabel] "branch end while"] >>|
-//        mapM_ g th >>|
-//        tell [Instr "bra" [L startLabel] "branch start while"] >>|
-//        tell [Lab endLabel]
-//    g (AssStmt (VarDef k fs) e) = 
-//        g e >>|
-//        abort "Shit, an assignment, figure out something with storing vars or something"
-//        //vars will be on stack in locals (possible pointers to heap)
-//    g (FunStmt _ _) = abort "CodeGen, FunStmt unused" //not used
+    g (IfStmt cond th el) = 
+        fresh >>= \elseLabel->
+        fresh >>= \endLabel->
+        g cond >>|
+        tell [Instr "brf" [L elseLabel] "branch else"] >>|
+        mapM_ g th >>|
+        tell [Instr "bra" [L endLabel] "branch end if"] >>|
+        tell [Lab elseLabel] >>|
+        mapM_ g el  >>|
+        tell [Lab endLabel]
+    g (WhileStmt cond th) = 
+        fresh >>= \startLabel->
+        fresh >>= \endLabel ->
+        tell [Lab startLabel] >>|
+        g cond >>|
+        tell [Instr "brf" [L endLabel] "branch end while"] >>|
+        mapM_ g th >>|
+        tell [Instr "bra" [L startLabel] "branch start while"] >>|
+        tell [Lab endLabel]
+    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 (ADDR t) = tell [Instr "stl" [Lit t] ""]
+    g (FunStmt k es) = mapM_ g es 
+        >>| jump "bsr" k
+        >>| mapM_ (const $ tell [Instr "ajs" [Lit -1] ""]) es //clean up args
+        >>| pure ()
     g (ReturnStmt Nothing) = tell [Instr "unlink" [] ""]
                >>| tell [Instr "ret" [] ""]
     g (ReturnStmt (Just e)) = g e
@@ -165,45 +190,30 @@ 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)
+addVars [] = id
+addVars [x:xs] = \ab->extend x (ADDR (-2 - (length xs))) (addVars xs ab)
+
 instance g FunDecl where
-    g (FunDecl _ k _ _ vds stms) = 
+    g (FunDecl _ k args _ vds stms) = 
         //varDecls can call the enclosing function, so first reserve a label for it 
         updateAdressbook (extend k (LAB k)) >>|
+        getAdressbook >>= \oldMap ->
+               updateAdressbook (addVars args) >>|
         tell [Lab k] >>|
                tell [Instr "link" [Lit 0] ""] >>|
-        //then generate functions for the VarDecls
-        getAdressbook >>= \oldMap ->
+        //add the vars
         foldM foldVarDecl 1 vds  >>|
-        //then the main function 
+        //and the statements
         mapM_ g stms >>|
         updateAdressbook (const oldMap) >>| pure ()
-//
-//load :: String -> Gen Instr
-//load k = genMap >>= \g-> case 'Map'.member k g of
-//    False = liftT (Left $ Error $ concat ["PANIC: ", k, " not found in variable mapping"])
-//    True = loadP $ 'Map'.find k g
-//
-//loadP :: LoadPlace -> Gen Instr
-//loadP pl = dec pl >>= \(instr, arg)-> pure $ Instr instr [arg] ""
-//where
-//    dec (LDA i) = pure ("lda", Lit i)
-//    dec (LDC i) = pure ("ldc", Lit i)
-//    dec (LDH i) = pure ("ldh", Lit i)
-//    dec (LDL i) = pure ("ldl", Lit i)
-//    dec (LDR i) = pure ("ldr", Lit i)
-//    dec (LDS i) = pure ("lds", Lit i)
-//    dec _       = liftT (Left $ Error "PANIC: trying to load non adres")
-//
-////Instruction (String), key of function to jump to    
-//jump :: String String -> Gen Instr
-//jump instr k = genMap >>= \g-> case 'Map'.member k g of
-//    False = liftT (Left $ Error $ concat ["PANIC: ", k, " not found as function"])
-//    True = dec ('Map'.find k g) >>= \lbl-> pure $ Instr instr [lbl] (k +++"()") 
-//where
-//    dec (FUNC l) = pure (L l)
-//    dec _ = liftT (Left $ Error "PANIC: trying to jump to non label")
+
+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]