X-Git-Url: http://wien.tomnetworks.com/gitweb/?a=blobdiff_plain;f=3a_asm%2FDT.hs;h=d4ad4901ea6130abd1550fd430a923e1dd639a14;hb=d3e96fef52bbd1c7fc4acf85561e9a4874016283;hp=3b22543c770e189246d1b43b55db20a3bdf8a167;hpb=0df70b557af4fd0550f0db2aa56fa3d89828d0a2;p=calu.git diff --git a/3a_asm/DT.hs b/3a_asm/DT.hs index 3b22543..d4ad490 100644 --- a/3a_asm/DT.hs +++ b/3a_asm/DT.hs @@ -3,7 +3,7 @@ module DT where import DTFormat import Expr_eval -import Prelude hiding (and,or) +import Prelude hiding (not,and,or) import Data.Bits hiding (xor) import qualified Data.Map as Map @@ -32,11 +32,25 @@ testins input = comma = char ',' mnem m = string m -iLit :: Dict -> Parser Word32 -iLit (_,d) = expr d +iLabel :: Dict -> Parser Word32 +-- TODO: save msb (=sign) correctly... +iLabel d@(aktadr,_) = do {i <- (iLit d); return $ (i - aktadr) .&. 0xffff} +iLit :: Dict -> Parser Word32 +iLit (_,d) = do + val <- expr d; + try (do { + string "@hi"; parseMySpaces; + return $ shiftR val 16 + }) <|> do { + string "@lo"; parseMySpaces; + return $ val .&. 0xffff + } <|> do {parseMySpaces; return val} + + +iLit5 d = do i <- iLit d; return $ i .&. 0x001f iLit12 d = do i <- iLit d; return $ i .&. 0x0fff -iLit15 d = do i <- iLit d; return $ i .&. 0xefff +iLit15 d = do i <- iLit d; return $ i .&. 0x7fff iLit16 d = do i <- iLit d; return $ i .&. 0xffff imm4 :: Parser String @@ -80,18 +94,27 @@ branchpred = do shiftArith :: Parser Word32 shiftArith = do { char 'a'; return 1} <|> do {string ""; return 0} +parseBracketClose :: Parser Char +parseBracketClose = do { c <- char ')'; parseMySpaces; return c} + (<.>) p n = p<*comma<*>n (<%>) p n = p<*space<*>n -(<@>) p n = p<*char '('<*>n<*char ')' +(<@>) p n = p<*char '('<*>n<*parseBracketClose infixl 1 <.> infixl 1 <%> infixl 1 <@> ins m form e = do {mnem m; form e} -csv0i_p dict f = f<$>condition<*>branchpred<*>(iLit dict) +csv0i_p dict f = f<$>condition<*>branchpred<*>(iLabel dict) csv0i_p' f = f<$>condition<*>branchpred +csv1 f = f<$>condition<%>reg +csv1_p f = f<$>condition<%>reg +csv2 f = f<$>condition<%>reg<.>reg +csv2i dict f = f<$>condition<%>reg<.>(iLit16 dict) csv2_scd f = f<$>sign<*>carry<*>updateDisable<*>condition<%>reg<.>reg csv2m dict f = f<$>condition<%>reg<.>(iLit15 dict)<@>reg +csv2i_cd dict f = f<$>carry<*>updateDisable<*>condition<%>reg<.>reg<.>(iLit5 dict) +csv2i_d dict f = f<$>updateDisable<*>condition<%>reg<.>reg<.>(iLit5 dict) 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) @@ -99,18 +122,16 @@ csv3_cd f = f<$>carry<*>updateDisable<*>condition<%>reg<.>reg<.>reg csv3_d f = f<$>updateDisable<*>condition<%>reg<.>reg<.>reg instructions = [add, addi, mov, sub, subi, - and, andx, - --, or, orx, xor, xorx,not] - -- pop, push, disc, fetch - -- movpf, movsf, movpt, movst - -- ldh, ldb - ldw, ldi, - -- stw, sth, stb - -- ldx, stx - -- call, reti - br, ret - -- brr, callr - -- cmp, cmpi + and, andx, or, orx, xor, xorx, not, + lls, lrs, ars, + pop, push, disc, fetch, + movpf, movsf, movpt, movst, + ldh, ldb, ldw, ldi, + stw, sth, stb, + ldx, stx, + br, ret, call, reti, + brr, callr, + cmp, cmpi ] -- arithmetic @@ -122,14 +143,42 @@ subi dict = ins "subi" (csv2i_scd dict) $ aformi 0x03 -- logic and _ = ins "and" csv3_d $ aform 0x04 0 andx dict = ins "andx" (csv2i_lfd dict) $ lformi 0x05 +or _ = ins "or" csv3_d $ aform 0x06 0 +orx dict = ins "orx" (csv2i_lfd dict) $ lformi 0x07 +xor _ = ins "xor" csv3_d $ aform 0x08 0 +xorx dict = ins "xorx" (csv2i_lfd dict) $ lformi 0x09 +not _ = ins "not" csv1 $ lformi'not 0x09 +lls dict = ins "lls" (csv2i_cd dict) $ shiform 0x0a 0 0 +lrs dict = ins "lrs" (csv2i_cd dict) $ shiform 0x0a 1 0 +ars dict = ins "ars" (csv2i_d dict) $ shiform 0x0a 1 1 0 -- memory +pop _ = ins "pop" csv1 $ sform 0x0b 0x0 +disc _ = ins "disc" csv1 $ sform 0x0b 0x1 +fetch _ = ins "fetch" csv1 $ sform 0x0b 0x2 +push _ = ins "push" csv1 $ sform 0x0b 0x3 +movpf _ = ins "movpf" csv1 $ sform 0x0c 0x2 +movsf _ = ins "movsf" csv1 $ sform 0x0c 0x0 +movpt _ = ins "movpt" csv1 $ sform 0x0d 0x2 +movst _ = ins "movst" csv1 $ sform 0x0d 0x0 ldw dict = ins "ldw" (csv2m dict) $ mformi 0x0e +ldh dict = ins "ldh" (csv2m dict) $ mformi 0x10 +ldb dict = ins "ldb" (csv2m dict) $ mformi 0x12 ldi dict = ins "ldi" (csv2i_sl dict) $ lformi' 0x1a +stw dict = ins "stw" (csv2m dict) $ mformi 0x0f +sth dict = ins "sth" (csv2m dict) $ mformi 0x11 +stb dict = ins "stb" (csv2m dict) $ mformi 0x13 +ldx dict = ins "ldx" (csv2m dict) $ mformi 0x14 +stx dict = ins "stx" (csv2m dict) $ mformi 0x15 -- 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 +call dict = ins "call" (csv0i_p dict) $ bform 0x16 0x1 1 ret _ = ins "ret" csv0i_p' $ bform' 0x16 0x2 reti _ = ins "reti" csv0i_p' $ bform' 0x16 0x3 +brr _ = ins "brr" csv1_p $ brrform 0x17 0 +callr _ = ins "callr" csv1_p $ brrform 0x17 1 +cmp _ = ins "cmp" csv2 $ mformi' 0x18 +cmpi dict = ins "cmpi" (csv2i dict) $ lformi 0x19 0 0 0 -- instruction formats aform opcd c d cond rd ra rb = pack [(cond,28),(opcd,23),(rd,19),(ra,15),(rb,11),(free,2),(c,1),(d,0)] @@ -140,13 +189,21 @@ aformi' opcd s c d cond rd ra = aformi opcd s c d cond rd ra 0 lformi opcd hl f d cond rd imm = pack [(cond,28),(opcd,23),(rd,19),(imm,3),(hl,2),(f,1),(d,0)] lformi' opcd s hl cond rd imm = lformi opcd s hl 0 cond rd imm +lformi'not opcd cond rd = lformi opcd 0 1 0 cond rd 0xefffffff mformi opcd cond rd disp ra = pack [(cond,28),(opcd,23),(rd,19),(ra,15),(disp,0)] +mformi' opcd cond rd = mformi opcd cond rd 0 bform opcd typ s cond bp imm = pack [(cond,28),(opcd,23),(imm,7),(free,4),(typ,2),(bp,1),(s,0)] where free = 0 bform' opcd typ cond bp = bform opcd typ 0 cond bp 0 +sform opcd typ cond rd = pack [(cond,28),(opcd,23),(rd,19),(typ,17)] + +brrform opcd typ cond ra = pack [(cond,28),(opcd,23),(ra,19),(typ,2)] + +shiform opcd lr a c d cond rd ra imm = pack [(cond,28),(opcd,23),(rd,19),(ra,15),(imm,10),(lr,3),(a,2),(c,1),(d,0)] + -- ppc64 stuff (TODO: remove) iform opcd aa lk li = pack [(opcd,6),(li,30),(aa,31),(lk,0)] scform opcd lev = pack [(opcd,6),(lev,27),(1,31)]