-- as for deep thoughts ISA ----------------------------------------------------------------------------- module Main where import DT import DTFormat import Control.Applicative hiding ((<|>),many) import System.IO import System.Environment import Text.Printf import Text.Parsec import Text.Parsec.String import Text.Parsec.Combinator import qualified Data.Map as M import Data.List import Data.Word import qualified Data.ByteString.Lazy as BL -- import Data.Binary.Put main :: IO () main = do args <- getArgs content <- getContents let src = (filter (((/=) "") . snd) $ (zip [1..] (lines content))) let (dict,formatedsrc) = convertDTF src 0x00 0x00 init_labels print args print formatedsrc {- case runParser DT.parseInstructions () "stdin" src of Left err -> print err Right val -> do sequence_ [printf "0x%08X\n" x | x <- val] -} type Counter = Word32 inc :: Counter -> Counter inc = ((+) 4) setabsolute :: Counter -> Counter setabsolute x = x type DictLabel = (String -> Word32) init_labels :: DictLabel init_labels _ = 0xffffffff add_label :: DictLabel -> (String,Word32) -> DictLabel add_label dic (s,w) | dic s /= 0xffffffff = error ("Label " ++ s ++ " already exists") | otherwise = newdict where newdict str | str == s = w | otherwise = dic str convertDTF :: [(Int,String)] -> Counter -> Counter -> DictLabel -> (DictLabel, [DTF]) convertDTF [] _ _ d = (d,[]) convertDTF ((lno,str):xs) datacnt instrcnt dict = (newdict, (DTF_Comment str):next) where (newdict,next) = convertDTF xs (inc datacnt) (inc instrcnt) dict testDTF :: String -> IO () testDTF input = case (parse parseDTFLine "" (input++"\n")) of Left err -> do { putStr "failz"; print err} Right x -> do { print x } parseDTFLine :: Parser DTF parseDTFLine = foldl1 (<|>) (fmap try lineFormats) <* char '\n' lineFormats = [lf_data, lf_comment, lf_label, lf_toparse, lf_org] lf_data = do string "data"; return $ DTF_Comment "lolz0" lf_comment = do skipMany space char ';' comment <- many $ noneOf ['\n'] newline return $ DTF_Comment comment lf_label = do string "label"; return $ DTF_Comment "lolz1" lf_toparse = do string "toparse"; return $ DTF_Comment "lolz2" lf_org = do string "org"; return $ DTF_Comment "lolz3"