import StdOverloaded
import StdString
from StdFunc import id
+import StdTuple
import Data.Func
import qualified Data.Map as Map
import Data.List
import Data.Either
+import Data.Tuple
import Data.Functor
import Control.Applicative
import Control.Monad
//Instruction is an instruction, with possible arguments and a possible comment
//Or is a label
:: Instr = Instr String [Arg] String
- | Label String
-:: Arg = L String | Lit Int
+ | Lab String
+:: Label :== String
+:: Arg = L Label | Lit Int
:: SSMProgram :== [Instr]
gen :: AST -> String
-gen _ = toString [Label "Test"
+gen _ = toString [Lab "Test"
,Instr "ldc" [Lit 1] "Eerste instructie"
,Instr "ldc" [Lit 2] "Tweede instructie"]
:: GenMap :== 'Map'.Map String LoadPlace
:: LoadPlace = LDA Int | LDC Int | LDH Int | LDL Int
| LDR Int | LDS Int
-:: Gen a :== StateT (GenMap) (Either GenError) a
+:: Gen a :== StateT (GenMap, [Label]) (Either GenError) a
genMap :: Gen GenMap
-genMap = gets id
+genMap = gets fst
class g a :: a -> Gen SSMProgram
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 = pure (loadP $ 'Map'.find k g)
+ True = loadP $ 'Map'.find k g
-loadP :: LoadPlace -> Instr
-loadP pl = let (instr, arg) = dec pl in Instr instr [Lit arg] ""
+loadP :: LoadPlace -> Gen Instr
+loadP pl = dec pl >>= \(instr, arg)-> pure $ Instr instr [arg] ""
where
- dec (LDA i) = ("lda", i)
- dec (LDC i) = ("ldc", i)
- dec (LDH i) = ("ldh", i)
- dec (LDL i) = ("ldl", i)
- dec (LDR i) = ("ldr", i)
- dec (LDS i) = ("lds", i)
+ 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")
class print a :: a -> [String]
instance print Instr where
- print (Label l) = [l, ":", "\n"]
+ print (Lab l) = [l, ":", "\n"]
print (Instr i args com) = ["\t", i] ++ print args ++ [" ;", com, "\n"]
instance print [Arg] where
instance toString SSMProgram where
toString p = concat $ intersperse " " $ map (\i-> concat $ intersperse " " $ print i) p
-instance MonadTrans (StateT GenMap) where
+instance MonadTrans (StateT (GenMap,[Label])) where
liftT m = StateT \s-> m >>= \a-> return (a, s)
\ No newline at end of file