3a_asm: using Expr in both stages
[calu.git] / 3a_asm / DT.hs
index 7dee1c1662760c94b4316cef033a6da1b188440c..3b22543c770e189246d1b43b55db20a3bdf8a167 100644 (file)
@@ -1,6 +1,7 @@
 module DT where
 
 import DTFormat
+import Expr_eval
 
 import Prelude hiding (and,or)
 
@@ -31,19 +32,12 @@ testins input =
 comma = char ','
 mnem m = string m
 
-iLabel :: Dict -> Parser Word32
-iLabel (addr,dict) = do
-       s <- foldl1 (<|>) (fmap (try . string . fst) dict)
-       let lab = get_elem s dict
-       return $ ((lab - addr) .&. 0xefff)
+iLit :: Dict -> Parser Word32
+iLit (_,d) = expr d
 
-iLit :: Parser Word32
-iLit = do { parseMySpaces; ret <- liftM read (many1 digit); parseMySpaces; return ret}
-
--- TODO: ...
-iLit12 = iLit
-iLit15 = iLit 
-iLit16 = iLit 
+iLit12 d = do i <- iLit d; return $ i .&. 0x0fff
+iLit15 d = do i <- iLit d; return $ i .&. 0xefff
+iLit16 d = do i <- iLit d; return $ i .&. 0xffff
 
 imm4 :: Parser String
 imm4 = do
@@ -94,22 +88,16 @@ infixl 1 <%>
 infixl 1 <@>
 
 ins m form e  = do {mnem m; form e}
-csv0i_p dict f = f<$>condition<*>branchpred<*>(iLabel dict)
+csv0i_p dict f = f<$>condition<*>branchpred<*>(iLit dict)
 csv0i_p' f = f<$>condition<*>branchpred
 csv2_scd f = f<$>sign<*>carry<*>updateDisable<*>condition<%>reg<.>reg
-csv2m f = f<$>condition<%>reg<.>iLit15<@>reg
-csv2i_scd f = f<$>sign<*>carry<*>updateDisable<*>condition<%>reg<.>reg<.>iLit12
-csv2i_sl f = f<$>sign<*>highlow<*>condition<%>reg<.>iLit16
-csv2i_lfd f = f<$>highlow<*>fill<*>updateDisable<*>condition<%>reg<.>iLit16
+csv2m dict f = f<$>condition<%>reg<.>(iLit15 dict)<@>reg
+csv2i_scd dict f = f<$>sign<*>carry<*>updateDisable<*>condition<%>reg<.>reg<.>(iLit12 dict)
+csv2i_sl dict f = f<$>sign<*>highlow<*>condition<%>reg<.>(iLit16 dict)
+csv2i_lfd dict f = f<$>highlow<*>fill<*>updateDisable<*>condition<%>reg<.>(iLit16 dict)
 csv3_cd f = f<$>carry<*>updateDisable<*>condition<%>reg<.>reg<.>reg
 csv3_d f = f<$>updateDisable<*>condition<%>reg<.>reg<.>reg
 
--- ppc64 stuff (TODO: remove)
-v1 f = f<$>iLit
-csv4 f = f<$>iLit<.>iLit<.>iLit<.>iLit
-csv5 f = f<$>iLit<.>iLit<.>iLit<.>iLit<.>iLit
-
-
 instructions = [add, addi, mov, sub, subi,
        and, andx,
        --, or, orx, xor, xorx,not]
@@ -127,16 +115,16 @@ instructions = [add, addi, mov, sub, subi,
 
 -- arithmetic
 add _ = ins "add" csv3_cd $ aform 0x00
-addi _ = ins "addi" csv2i_scd $ aformi 0x02
+addi dict = ins "addi" (csv2i_scd dict) $ aformi 0x02
 mov _ = ins "mov" csv2_scd $ aformi' 0x02
 sub _ = ins "sub" csv3_cd $ aform 0x01
-subi _ = ins "subi" csv2i_scd $ aformi 0x03
+subi dict = ins "subi" (csv2i_scd dict) $ aformi 0x03
 -- logic
 and _ = ins "and" csv3_d $ aform 0x04 0
-andx _ = ins "andx" csv2i_lfd $ lformi 0x05
+andx dict = ins "andx" (csv2i_lfd dict) $ lformi 0x05
 -- memory
-ldw _ = ins "ldw" csv2m $ mformi 0x0e
-ldi _ = ins "ldi" csv2i_sl $ lformi' 0x1a
+ldw dict = ins "ldw" (csv2m dict) $ mformi 0x0e
+ldi dict = ins "ldi" (csv2i_sl dict) $ lformi' 0x1a
 -- misc
 -- set signed by default! in very rare cases this can be an issue.
 br dict = ins "br" (csv0i_p dict) $ bform 0x16 0x0 1