3a_asm: .define support
[calu.git] / 3a_asm / Main.hs
1 -- as for deep thoughts ISA
2 -----------------------------------------------------------------------------
3
4
5 import DT
6 import DTFormat
7
8 import Control.Applicative hiding ((<|>),many)
9
10 import System.IO
11 import System.Environment
12 import Text.Printf
13 import Text.Parsec
14 import Text.Parsec.String
15 import Text.Parsec.Combinator
16 import qualified Data.Map as M
17 import Data.List
18 import Data.Word
19 import qualified Data.ByteString.Lazy as BL
20 import Control.Monad
21
22
23 main :: IO ()
24 main = do
25         args <- getArgs
26         content <- getContents
27         let src = (filter (((/=) "") . snd) $ (zip [1..] (lines content)))
28         let (dict,formatedsrc) = convertDTF src NoState 0x00 0x00 []
29         printf "\nlabels:\n"
30         sequence_ [printf "%10s @ 0x%08x\n" l a | (l,a) <- (reverse dict)]
31         printf "\nparsed asm:\n"
32         sequence_ [printf "%s" (show x) | x <- formatedsrc]
33         let parsed = parseInstr dict formatedsrc
34         printf "\nafter parsing the instructions:\n"
35         sequence_ [printf "%s" (show x) | x <- parsed]
36
37
38 parseInstr :: [DictElem] -> [DTF] -> [DTF]
39 parseInstr _ [] = []
40 parseInstr dict ((DTF_InstrToParse a instr c l s):xs) =
41         (DTF_Instr a bytecode c l s):(parseInstr dict xs)
42         where
43         bytecode = case (parse (instruction (a,dict)) "" (instr++"\n")) of
44                 Left err -> error ("couldn't parse Instruction: " ++ instr ++ "\n" ++ show err)
45                 Right x -> x
46 parseInstr dict (x:xs) = x:(parseInstr dict xs)
47
48
49 type Counter = Word32
50
51 inc :: Counter -> Counter
52 inc = ((+) 4)
53
54
55 convertDTF :: [(Int,String)] -> DT_State -> Counter -> Counter -> [DictElem] -> ([DictElem], [DTF])
56 convertDTF [] _ _ _ d = (d,[])
57 convertDTF ((lno,str):xs) state datacnt instrcnt dict = (newdict, (actlist newdtf))
58         where
59         actlist (DTF_Org _) = next
60         actlist (DTF_State _) = next
61         actlist (DTF_Define _ _ _) = next
62         actlist y = y:next
63
64         (newdict,next) = convertDTF xs (nstate newdtf) (ndatacnt newdtf) (ninstrcnt newdtf) (ndict newdtf)
65
66         ndatacnt (DTF_Org adr)
67                 | state == InData = adr
68                 | otherwise = datacnt
69         ndatacnt (DTF_Data _ _ _ _ _) = inc datacnt
70         ndatacnt _ = datacnt
71
72         ninstrcnt (DTF_Org adr)
73                 | state == InText = adr
74                 | otherwise = instrcnt
75         ninstrcnt (DTF_Instr _ _ _ _ _) = inc instrcnt
76         ninstrcnt (DTF_InstrToParse _ _ _ _ _) = inc instrcnt
77         ninstrcnt _ = instrcnt
78
79         nstate (DTF_State s) = s
80         nstate _ = state
81
82         ndict (DTF_Label l _ a) = dict `add_elem` (l,a)
83         ndict (DTF_SectionToDet a _ _ l _) = dict `add_elem` (l,a)
84         ndict (DTF_InstrToParse a _ _ l _) = dict `add_elem` (l,a)
85         ndict (DTF_Data a _ _ l _) = dict `add_elem` (l,a)
86         ndict (DTF_Instr a _ _ l _) = dict `add_elem` (l,a)
87         ndict (DTF_Define l v _) = dict `add_elem` (l,v)
88         ndict _ = dict
89
90         newdtf = case (parse parseDTFLine "" (str++"\n")) of
91                 Left err -> error ("couldn't parse line " ++ (show lno) ++ ": " ++ (show err))
92                 Right (DTF_SectionToDet _ v c l s) ->
93                         case state of
94                                 NoState -> error "missing .data or .text"
95                                 InData -> (DTF_Data datacnt v c l s)
96                                 InText -> (DTF_Instr instrcnt v c l s)
97                 Right (DTF_InstrToParse _ v c l s) ->
98                         (DTF_InstrToParse instrcnt v c l s)
99                 Right y@(DTF_Org _) ->
100                         case state of
101                                 NoState -> error "missing .data or .text"
102                                 _ -> y
103                 Right (DTF_Label l c _) ->
104                         case state of
105                                 NoState -> error "missing .data or .text"
106                                 InData -> (DTF_Label l c datacnt)
107                                 InText -> (DTF_Label l c instrcnt)
108                 Right z -> z -- DTF_Comment, DTF_State, DTF_Define
109
110
111
112 testDTF :: String -> IO ()
113 testDTF input =
114         case (parse parseDTFLine "" (input++"\n")) of
115                 Left err -> do { putStr "failz ;(\n"; print err}
116                 Right x -> do { print x }
117
118 parseDTFLine :: Parser DTF
119 parseDTFLine = foldl1 (<|>) (fmap try lineFormats) <* char '\n'
120
121 lineFormats = [lf_define, lf_sdata, lf_stext, lf_org, lf_data, lf_comment, lf_toparse, lf_label]
122
123 -- helper
124 parseIdent :: Parser String
125 parseIdent = do
126         ident <- letter
127         idents <- many $ (letter <|> digit <|> char '_')
128         return $ (ident:idents)
129
130 parseLabel :: Parser String
131 parseLabel = do
132         l <- parseIdent
133         char ':'
134         return $ l
135
136 parseComment :: Parser String
137 parseComment = do
138         skipMany space
139         char ';'
140         comment <- many $ noneOf "\n"
141         return $ comment
142
143 parseConst :: Parser Word32
144 parseConst = do
145         skipMany space
146         -- TODO: only decimal and hex (since this is supported by read)
147         -- TODO: howto check too big values? atm they get truncated
148         str <- try(do pref <- string "0x"; z <- many1 hexDigit; return $ (pref ++ z)) <|> (many1 digit)
149         let val = read str
150         return $ val
151
152 -- teh pars0rs
153 lf_data = do
154         l <- try (parseLabel) <|> string ""
155         skipMany space
156         fill <- string ".fill "
157         -- TODO: atm 32bit imm only
158         code <- many1 $ noneOf "\n;"
159         -- TODO: this is quite ugly here :/
160         let (Right val) = parse parseConst "" code
161         comment <- try(parseComment) <|> parseMySpaces
162         return $ DTF_SectionToDet 0 val (fill ++ code) l comment
163
164 lf_comment = do
165         comment <- parseComment
166         return $ DTF_Comment comment
167
168 lf_label = do
169         l <- parseLabel
170         comment <- try(parseComment) <|> parseMySpaces
171         return $ DTF_Label l comment 0
172
173 lf_toparse = do
174         l <- try(parseLabel) <|> string ""
175         skipMany space
176         code <- many1 $ noneOf "\n;"
177         comment <- try(parseComment) <|> parseMySpaces
178         return $ DTF_InstrToParse 0 code code l comment
179
180 lf_org = do
181         skipMany space
182         string ".org"
183         val <- parseConst
184         parseMySpaces
185         return $ DTF_Org val
186
187 lf_sdata = do
188         skipMany space
189         string ".data"
190         parseMySpaces
191         return $ DTF_State InData
192
193 lf_stext = do
194         skipMany space
195         string ".text"
196         parseMySpaces
197         return $ DTF_State InText
198
199 lf_define = do
200         skipMany space
201         string ".define"
202         parseMySpaces
203         id <- parseIdent
204         parseMySpaces; char ','; parseMySpaces
205         ret <- parseConst
206         comment <- try(parseComment) <|> parseMySpaces
207         return $ DTF_Define id ret comment