import Data.Either
import Data.Tuple
import Data.Functor
+import Data.Monoid
import Control.Applicative
import Control.Monad
-import Control.Monad.State
import Control.Monad.Trans
from Text import class Text(concat), instance Text String
import AST
+import RWST
//Instruction is an instruction, with possible arguments and a possible comment
//Or is a label
+TRUE :== -1
+FALSE :== 0
:: Instr = Instr String [Arg] String
| Lab String
:: Label :== String
:: GenMap :== 'Map'.Map String LoadPlace
:: LoadPlace = LDA Int | LDC Int | LDH Int | LDL Int
| LDR Int | LDS Int
-:: Gen a :== StateT (GenMap, [Label]) (Either GenError) a
+ | FUNC Label
+:: Gen a :== RWST [Int] SSMProgram (GenMap, [Label]) (Either GenError) a
genMap :: Gen GenMap
genMap = gets fst
-class g a :: a -> Gen SSMProgram
+class g a :: a -> Gen ()
instance g Expr where
- g (VarExpr _ (VarDef k fs)) = pure <$> load k //note: pure is pure for list, i.e. []
+ g (VarExpr _ (VarDef k fs)) = load k >>= \instr-> tell [instr] //note: pure is pure for list, i.e. []
+ g (IntExpr _ i) = loadP (LDC i) >>= \instr-> tell [instr]
+ g (CharExpr _ c) = undef //how to deal with strings?
+ g (BoolExpr _ True) = loadP (LDC TRUE) >>= \instr-> tell [instr]
+ g (BoolExpr _ False) = loadP (LDC FALSE) >>= \instr-> tell [instr]
+ g (Op2Expr _ e1 op e2) = g e1 >>| g e2 >>| tell [Instr (op2ins op) [] ""]
+
+op2ins :: Op2 -> String
+op2ins op = case op of
+ BiPlus = "add"
+ BiMinus = "sub"
+ BiTimes = "mul"
+ BiDivide = "div"
+ BiMod = "mod"
+ BiEquals = "eq"
+ BiLesser = "lt"
+ BiGreater = "gt"
+ BiLesserEq = "le"
+ BiGreaterEq = "ge"
+ BiUnEqual = "ne"
+ BiAnd = "and"
+ BiOr = "or"
+ BiCons = abort "Shit, Cons, how to deal with this?"
load :: String -> Gen Instr
load k = genMap >>= \g-> case 'Map'.member k g of
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")
+
class print a :: a -> [String]
instance print Instr where
toString (Lit int) = toString int
instance toString SSMProgram where
- toString p = concat $ intersperse " " $ map (\i-> concat $ intersperse " " $ print i) p
-
-instance MonadTrans (StateT (GenMap,[Label])) where
- liftT m = StateT \s-> m >>= \a-> return (a, s)
\ No newline at end of file
+ toString p = concat $ intersperse " " $ map (\i-> concat $ intersperse " " $ print i) p
\ No newline at end of file