Improved Let syntax and improvements to type system
[cc1516.git] / gen.icl
diff --git a/gen.icl b/gen.icl
index 2828798..e92954c 100644 (file)
--- a/gen.icl
+++ b/gen.icl
@@ -33,7 +33,7 @@ FALSE :== 0
 :: SSMProgram :== [Instr]
 :: GenError = Error String
 :: Addressbook :== 'Map'.Map String Address
-:: Address = LAB String Int Int | ADDR Int
+:: Address = LAB String Int Int | ADDR Int Int
 :: Gen a :== RWST () SSMProgram (Addressbook, [Label]) (Either GenError) a
 
 labelStream :: [Label]
@@ -72,11 +72,12 @@ programContext x = [Lab "1func"
                fS :: [String] Int -> SSMProgram
                fS [] _ = []
                fS [k:xs] n = [
-                        Instr "lds" [Lit 0] ""
+                        Lab $ "1next" +++ toString n
+                       ,Instr "ldr" [Raw "R5"] ""
                        ,Instr "ldc" [Lit n] $ "branch to: " +++ k
                        ,Instr "eq" [] ""
-                       ,Instr "ajs" [Lit -1] ""
-                       ,Instr "bsr" [L k] ""
+                       ,Instr "brf" [L $ "1next" +++ (toString $ n + 1)] ""
+                       ,Instr "bra" [L k] ""
                        :fS xs $ n+1]
                context :: SSMProgram
                context =   [Lab "1printint"
@@ -170,15 +171,15 @@ instance g Expr where
                >>| g e2
                >>| tell [Instr "stmh" [Lit 2] ""]
     g (VarExpr _ (VarDef k fs)) = getAdressbook >>= \ab->case 'Map'.get k ab of
-               Just (ADDR t) = tell [Instr "ldl" [Lit t] ""] >>| mapM_ g fs >>| pure ()
+               Just (ADDR t arity) = tell [Instr "ldl" [Lit t] ""] >>| mapM_ g fs >>| pure ()
                Just (LAB l _ fn) = tell 
                        [Instr "ldc" [Lit fn] ""
-                       ,Instr "sth" [] ""
                        ,Instr "ldc" [Lit 0] ""
-                       ,Instr "sth" [] ""]
+                       ,Instr "stmh" [Lit 2] ""]
     g (FunExpr _ k es fs) = getAdressbook >>= \ab->case 'Map'.get k ab of
                //Identifier points to function
                Just (LAB l arity fn) = if (arity <> (length es))
+                       //Function is not complete
                        (       tell
                                        [Instr "ldc" [Lit fn] "Store function number"
                                        ,Instr "sth" [] ""
@@ -189,20 +190,113 @@ instance g Expr where
                                >>| if (isEmpty es) (pure ()) (tell 
                                        [Instr "stmh" [Lit $ length es] "Store arguments"
                                        ,Instr "ajs" [Lit -1] ""]))
+                       //Function is complete
                        (       mapM_ g es
                                >>| jump "bsr" k
                        >>| tell 
                                        [Instr "ajs" [Lit $ ~(length es)] "Clean arguments"
                                        ,Instr "ldr" [Raw "RR"] ""])
                //Identifier points to variable, thus higher order function
-               Just (ADDR t) = liftT (Left $ Error "FunExpr to addr")
+               Just (ADDR t arity) = if (arity <> (length es))
+                       //Function is still  not complete
+                       ( fresh >>= \finish->fresh >>= \start->tell [
+                               //Store function number
+                                Instr "ldl" [Lit t] "STARTING HIGHER ORDER UPDATE"
+                               ,Instr "ldh" [Lit 0] "get function number"
+                               ,Instr "sth" [] "Store"
+                               //Store function arity
+                               ,Instr "ldl" [Lit t] "get pointer again"
+                               ,Instr "ldh" [Lit 1] "get function arity"
+                               ,Instr "ldc" [Lit $ length es] "add argument number"
+                               ,Instr "add" [] "add"
+                               ,Instr "sth" [] "Store"
+                               ,Instr "ajs" [Lit -1] "Adjust pointer"
+                               //load the arguments
+                               ,Instr "ldl" [Lit t] ""
+                               ,Instr "ldh" [Lit 1] "Load available arguments"
+                               ,Instr "str" [Raw "R5"] "Store available args in register"
+                               ,Instr "ldc" [Lit 0] "Store offset"
+                               ,Instr "str" [Raw "R6"] "Store offset in register"
+                               ,Lab start
+                               ,Instr "ldr" [Raw "R5"] ""
+                               ,Instr "ldc" [Lit 0] ""
+                               ,Instr "eq" [] ""
+                               ,Instr "brt" [L finish] "Done pushing arg, bye"
+                               //Load heapadress
+                               ,Instr "ldl" [Lit t] ""
+                               ,Instr "ldr" [Raw "R6"] ""
+                               ,Instr "add" [] "Corrected heapaddress"
+                               ,Instr "ldh" [Lit 2] "Load argument"
+                               ,Instr "sth" [] "And store it immediatly after"
+                               //Decrease available arguments
+                               ,Instr "ldr" [Raw "R5"] ""
+                               ,Instr "ldc" [Lit 1] ""
+                               ,Instr "sub" [] ""
+                               ,Instr "str" [Raw "R5"] ""
+                               //Increase available arguments
+                               ,Instr "ldr" [Raw "R6"] ""
+                               ,Instr "ldc" [Lit 1] ""
+                               ,Instr "add" [] ""
+                               ,Instr "str" [Raw "R6"] ""
+                               ,Instr "bra" [L start] ""
+                               ,Lab finish
+                               ]
+                         >>| mapM_ g es
+                         >>| tell 
+                                       [Instr "stmh" [Lit $ length es] "Store extra args"
+                                       ,Instr "ajs" [Lit -1] ""]
+                       )
+                       //Function is complete
+                       ( fresh >>= \finish->fresh >>= \start->tell [
+                                Instr "ldl" [Lit t] "STARTING HIGHER ORDER CALL"
+                               ,Instr "ldh" [Lit 1] "Load available arguments"
+                               ,Instr "str" [Raw "R5"] "Store available args in register"
+                               ,Instr "ldc" [Lit 0] "Store offset"
+                               ,Instr "str" [Raw "R6"] "Store offset in register"
+                       
+                               ,Lab start
+                               ,Instr "ldr" [Raw "R5"] ""
+                               ,Instr "ldc" [Lit 0] ""
+                               ,Instr "eq" [] ""
+                               ,Instr "brt" [L finish] "Done pushing arg, bye"
+                               //Load heapadress
+                               ,Instr "ldl" [Lit t] ""
+                               ,Instr "ldr" [Raw "R6"] ""
+                               ,Instr "add" [] "Corrected heapaddress"
+                               ,Instr "ldh" [Lit 2] "Load argument"
+                               //Decrease available arguments
+                               ,Instr "ldr" [Raw "R5"] ""
+                               ,Instr "ldc" [Lit 1] ""
+                               ,Instr "sub" [] ""
+                               ,Instr "str" [Raw "R5"] ""
+                               //Increase available arguments
+                               ,Instr "ldr" [Raw "R6"] ""
+                               ,Instr "ldc" [Lit 1] ""
+                               ,Instr "add" [] ""
+                               ,Instr "str" [Raw "R6"] ""
+                               ,Instr "bra" [L start] ""
+                               ,Lab finish
+                               ]
+                         >>| mapM_ g es
+                         >>| tell
+                               [Instr "ldl" [Lit t] ""
+                               ,Instr "ldh" [Lit 0] "Get function number"
+                               ,Instr "str" [Raw "R5"] ""
+                               ,Instr "bsr" [L "1func"] ""
+                               ,Instr "ldr" [Raw "MP"] ""
+                               ,Instr "ldc" [Lit t] ""
+                               ,Instr "add" [] ""
+                               ,Instr "str" [Raw "SP"] ""
+                               ,Instr "ldr" [Raw "RR"] ""
+                               ]
+                       )
                Nothing = liftT (Left $ Error "Undefined function!!!")
 
 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 (ADDR t) = liftT (Left $ Error "Address as jump???")
+       Just (ADDR t arity) = abort "NO ADDRESS JUMPING FFS"
 
 instance g Stmt where
     g (IfStmt cond th el) = 
@@ -228,7 +322,7 @@ instance g Stmt where
         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] ""]
+            Just (ADDR t ar) = tell [Instr "stl" [Lit t] ""]
     g (FunStmt k es fs) = mapM_ g es 
         >>| jump "bsr" k
         >>| tell [Instr "ajs" [Lit (~(length es))] ""] //clean up args
@@ -243,18 +337,25 @@ instance g Stmt where
 foldVarDecl :: Int VarDecl -> Gen Int
 foldVarDecl x (VarDecl _ mt k e) = g e 
     >>| annote x k
-       >>| updateAdressbook (extend k (ADDR x))
+       >>| updateAdressbook (extend k (ADDR x $ arity $ fromJust mt))
        >>| pure (x + 1)
 
-addVars :: [String] -> (Addressbook -> Addressbook)
-addVars [] = id
-addVars [x:xs] = \ab->extend x (ADDR (-2 - (length xs))) (addVars xs ab)
+arity :: Type -> Int
+arity (_ ->> x) = 1 + arity x
+arity _ = 0
+
+addVars :: Type [String] -> (Addressbook -> Addressbook)
+addVars _ [] = id
+addVars (t ->> ts) [x:xs] = \ab->
+       extend x (ADDR (-2 - (length xs)) (arity t)) (addVars ts xs ab)
+addVars t [x] = \ab->
+       extend x (ADDR -2 0) ab
 
 instance g FunDecl where
-    g (FunDecl _ k args _ vds stms) = 
+    g (FunDecl _ k args mt vds stms) = 
         //varDecls can call the enclosing function, so first reserve a label for it 
         getAdressbook >>= \oldMap ->
-               updateAdressbook (addVars args) >>|
+               updateAdressbook (addVars (fromJust mt) args) >>|
         tell [Lab k] >>|
                tell [Instr "link" [Lit 0] ""] >>|
         //add the vars