import StdString
from StdFunc import id
import StdTuple
+import StdEnum
+from StdEnv import const
import Data.Func
import qualified Data.Map as Map
TRUE :== -1
FALSE :== 0
:: Instr = Instr String [Arg] String
- | Lab String
+ | Lab Label
:: Label :== String
:: Arg = L Label | Lit Int
:: SSMProgram :== [Instr]
-
-
-gen :: AST -> String
-gen _ = toString [Lab "Test"
- ,Instr "ldc" [Lit 1] "Eerste instructie"
- ,Instr "ldc" [Lit 2] "Tweede instructie"]
-
-
-//Scrap this, we'll need shared state when generating
-//i.e. to figure out the positions of vars relative to the
-//SP/MP/whatever or in which register they are
-//and to supply with fresh labels
-
-//The generation monad
:: GenError = Error String
:: GenMap :== 'Map'.Map String LoadPlace
:: LoadPlace = LDA Int | LDC Int | LDH Int | LDL Int
| LDR Int | LDS Int
| FUNC Label
-:: Gen a :== RWST [Int] SSMProgram (GenMap, [Label]) (Either GenError) a
+:: Gen a :== RWST Label SSMProgram (GenMap, [Label]) (Either GenError) a
+
+labelStream :: [Label]
+labelStream = map (\i-> concat ["lab_", toString i]) [1..]
+gen :: AST -> String
+gen _ = prog
+ where
+ expr = (Op2Expr zero (Op1Expr zero UnMinus (IntExpr zero 4)) BiPlus (IntExpr zero 7))
+ expr2 = (FunExpr zero "test" [IntExpr zero 4] [])
+ stmt = (IfStmt (BoolExpr zero True) [] [])
+ prog = case evalRWST (g stmt) "end" ('Map'.newMap, labelStream) of
+ Left (Error e) = abort e
+ Right (_, prog) = toString prog
+//gen _ = toString [Lab "Test"
+// ,Instr "ldc" [Lit 1] "Eerste instructie"
+// ,Instr "ldc" [Lit 2] "Tweede instructie"]
+
+
+//helper functions for the gen monad
genMap :: Gen GenMap
genMap = gets fst
+fresh :: Gen Label
+fresh = gets snd >>= \vars->
+ modify (appSnd $ const $ tail vars) >>|
+ pure (head vars)
+
class g a :: a -> Gen ()
instance g Expr where
g (Op1Expr _ UnMinus e) = g e >>| tell [Instr "neg" [] ""]
g (EmptyListExpr _) = abort "Shit, empty list expr"
g (TupleExpr p (e1,e2)) = abort "How to deal with tuples?"
- g (FunExpr _ k es fs) = mapM g es >>| jump "bra" k >>= \instr-> tell [instr]
+ g (FunExpr _ k es fs) = mapM g es >>| jump "bsr" k >>= \instr-> tell [instr]
+ //bra is probably not right, figure out function call way
+
+instance g Stmt where
+ g (IfStmt cond th el) =
+ fresh >>= \elseLabel->
+ fresh >>= \endLabel->
+ g cond >>|
+ tell [Instr "brf" [L elseLabel] "branch false"] >>|
+ mapM_ g th >>|
+ tell [Instr "bra" [L endLabel] "branch end if"] >>|
+ tell [Lab elseLabel] >>|
+ mapM_ g el >>|
+ tell [Lab endLabel]
+
op2ins :: Op2 -> String
op2ins op = case op of