diff options
Diffstat (limited to 'SHARC/Types.hs')
-rw-r--r-- | SHARC/Types.hs | 184 |
1 files changed, 184 insertions, 0 deletions
diff --git a/SHARC/Types.hs b/SHARC/Types.hs new file mode 100644 index 0000000..47e4686 --- /dev/null +++ b/SHARC/Types.hs @@ -0,0 +1,184 @@ +{- + This file is part of shark-disassembler. + + Copyright (C) 2014 Ricardo Wurmus + + This program is free software: you can redistribute it and/or modify + it under the terms of the GNU General Public License as published by + the Free Software Foundation, either version 3 of the License, or + (at your option) any later version. + + This program is distributed in the hope that it will be useful, + but WITHOUT ANY WARRANTY; without even the implied warranty of + MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + GNU General Public License for more details. + + You should have received a copy of the GNU General Public License + along with this program. If not, see <http://www.gnu.org/licenses/>. +-} + +module SHARC.Types where + +import SHARC.Word48 + +import Data.Word +import Data.Map (fromList, findWithDefault) +import Data.Bits ((.&.), (.|.), xor, testBit, shift, shiftR) +import Text.Printf (printf) + +-- TODO: check other register assigments as well! They may need to be shifted first. + + +data Cond = Cond Word8 +-- the 5 bit condition codes are at an odd position in the byte, so we +-- have to cut them out [ 00111110 ] +-- TODO: valid values go from 0 to 31, restrict! +mkCond :: Word48 -> Cond +mkCond w = Cond $ w64 `cutMask` 0x003E00000000 + where + w64 = word48ToWord64 w + +data TermCond = TermCond Word8 +-- the 5 bit condition codes are at an odd position in the byte, so we +-- have to cut them out [ 00111110 ] +-- TODO: valid values go from 0 to 31, restrict! +mkTermCond :: Word48 -> TermCond +mkTermCond w = TermCond $ w64 `cutMask` 0x003E00000000 + where + w64 = word48ToWord64 w + +-- from table 1-4 (isr.pdf) "Conditional Execution Codes Summary" +condCodes = [ + "EQ", + "NE", + "GT", + "LT", + "GE", + "LE", + "AC", + "NOT AC", + "AV", + "NOT AV", + "MV", + "NOT MV", + "MS", + "NOT MS", + "SV", + "NOT SV", + "SZ", + "NOT SZ", + "TF", + "NOT TF", + "FLAG0_IN", + "NOT FLAG0_IN", + "FLAG1_IN", + "NOT FLAG1_IN", + "FLAG2_IN", + "NOT FLAG2_IN", + "FLAG3_IN", + "NOT FLAG3_IN", + "BM", + "NOT BM", + "NOT ICE", + "TRUE" ] + +condCodeMap = fromList $ zip [0..] condCodes +termCodeMap = fromList $ zip [0..] $ (init . init) condCodes ++ ["LCE", "FOREVER"] + +instance Show Cond where + -- do not print if code is "TRUE" (31) + show (Cond n) = if n == 31 then "" + else "IF " ++ findWithDefault (printf "0x%02X" n) n condCodeMap ++ " " + +instance Show TermCond where + show (TermCond n) = findWithDefault (printf "0x%02X" n) n termCodeMap + + +data Ireg = Ireg Word8 +mkIreg :: Word8 -> Ireg +mkIreg n = Ireg $ n .&. 0x07 +instance Show Ireg where + show (Ireg n) = printf "I%d" n + +data Mreg = Mreg Word8 +mkMreg :: Word8 -> Mreg +mkMreg n = Mreg $ n .&. 0x07 +instance Show Mreg where + show (Mreg n) = printf "M%d" n + +-- TODO: see table 1-8 and 1-11 in isr.pdf +-- 7 bit universal register +data Ureg = Ureg Word8 +mkUreg :: Word8 -> Ureg +mkUreg n = Ureg $ n .&. 0xEF +instance Show Ureg where + show (Ureg n) = printf "0x%02X" n + +-- 4 bit system register +data Sreg = Sreg Word8 +mkSreg :: Word8 -> Sreg +mkSreg n = Sreg $ n .&. 0x0F +instance Show Sreg where + show (Sreg n) = printf "0x%01X" n + +-- 4 bit data register +data Dreg = Dreg Word8 +mkDreg :: Word8 -> Dreg +mkDreg n = Dreg $ n .&. 0x0F +instance Show Dreg where + show (Dreg n) = printf "R%d" n -- TODO: according to the docs this is R15-R0 *and* F15-F0 + +data Address24 = Address24 Word32 -- absolute 24 bit address + | RelAddress24 Word32 -- relative 24 bit address +data Address32 = Address32 Word32 -- absolute 32 bit address + | RelAddress32 Word32 -- relative 24 bit address + +instance Show Address24 where + show (Address24 w) = printf "0x%06X" w + show (RelAddress24 w) = printf "(PC,%s)" w' -- two's complement + where w' = if w `testBit` 23 then '-' : show (w `xor` 0xFFFFFF) else show w + +instance Show Address32 where + show (Address32 w) = printf "0x%08X" w + show (RelAddress32 w) = printf "(PC,%s)" w' -- two's complement + where w' = if w `testBit` 31 then '-' : show (w `xor` 0xFFFFFFFF) else show w + + +toWord32 :: (Word8, Word8, Word8, Word8) -> Word32 +toWord32 (a,b,c,d) = fromIntegral a `shift` 24 .|. + fromIntegral b `shift` 16 .|. + fromIntegral c `shift` 8 .|. + fromIntegral d + +data Update = PreModify -- 0, no update + | PostModify -- 1, with update + +-- TODO: check again Table 1-7 Opcode Acronyms to be sure that the mapping order is right! +type PushPops = ([String], [String]) + +data Memory = Data -- data memory + | Prog -- programme memory + deriving Show +data AccessType = Read | Write -- memory acces + deriving Show +data WordAccess = NW | LW -- LW forces a long word access when address is in normal word address + deriving Show + +data BranchAbsRel = Abs -- direct branch (absolute address) + | Rel -- PC-relative branch + deriving Show + +data BranchType = Jump + | Call + deriving Show + +data ReturnSource = Subroutine + | Interrupt + deriving Show + +data BitOp = SET + | CLR + | TGL + | TST + | XOR + deriving Show |