3a_asm: parse a comment \o/
[calu.git] / 3a_asm / Main.hs
1 -- as for deep thoughts ISA
2 -----------------------------------------------------------------------------
3
4 module Main where
5
6 import DT
7 import DTFormat
8
9 import Control.Applicative hiding ((<|>),many)
10
11 import System.IO
12 import System.Environment
13 import Text.Printf
14 import Text.Parsec
15 import Text.Parsec.String
16 import Text.Parsec.Combinator
17 import qualified Data.Map as M
18 import Data.List
19 import Data.Word
20 import qualified Data.ByteString.Lazy as BL
21 -- import Data.Binary.Put
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 0x00 0x00 init_labels
29         print args
30         print formatedsrc
31
32 {-
33         case runParser DT.parseInstructions () "stdin" src of
34                 Left err -> print err
35                 Right val -> do
36                         sequence_ [printf "0x%08X\n" x | x <- val]
37 -}
38
39 type Counter = Word32
40
41 inc :: Counter -> Counter
42 inc = ((+) 4)
43
44 setabsolute :: Counter -> Counter
45 setabsolute x = x
46
47
48 type DictLabel = (String -> Word32)
49
50 init_labels :: DictLabel
51 init_labels _ = 0xffffffff
52
53 add_label :: DictLabel -> (String,Word32) -> DictLabel
54 add_label dic (s,w)
55         | dic s /= 0xffffffff = error ("Label " ++ s ++ " already exists")
56         | otherwise = newdict
57         where
58         newdict str
59                 | str == s = w
60                 | otherwise = dic str
61
62
63 convertDTF :: [(Int,String)] -> Counter -> Counter -> DictLabel -> (DictLabel, [DTF])
64 convertDTF [] _ _ d = (d,[])
65 convertDTF ((lno,str):xs) datacnt instrcnt dict =
66         (newdict, (DTF_Comment str):next)
67         where
68         (newdict,next) = convertDTF xs (inc datacnt) (inc instrcnt) dict
69
70 testDTF :: String -> IO ()
71 testDTF input =
72         case (parse parseDTFLine "" (input++"\n")) of
73                 Left err -> do { putStr "failz"; print err}
74                 Right x -> do { print x }
75
76 parseDTFLine :: Parser DTF
77 parseDTFLine = foldl1 (<|>) (fmap try lineFormats) <* char '\n'
78
79 lineFormats = [lf_data, lf_comment, lf_label, lf_toparse, lf_org]
80
81 lf_data = do string "data"; return $ DTF_Comment "lolz0"
82
83 lf_comment = do
84         skipMany space
85         char ';'
86         comment <- many $ noneOf ['\n']
87         newline
88         return $ DTF_Comment comment
89
90 lf_label = do string "label"; return $ DTF_Comment "lolz1"
91 lf_toparse = do string "toparse"; return $ DTF_Comment "lolz2"
92 lf_org = do string "org"; return $ DTF_Comment "lolz3"