module Micro.Asm.Sdcc where import qualified Micro.Ast as A toIdent :: A.Ident -> String toIdent id = "_" ++ id toLabel :: A.Ident -> Bool -> String toLabel id False = toIdent id ++ "::" toLabel id True = toIdent id ++ ":" toData :: A.Type -> String toData (A.Type t) | t == "bool" || t == "u8" || t == "s8" = ".ds 1" | t == "u16" || t == "s16" = ".ds 2" | otherwise = ".ds 2" toData (A.FuncType _ _) = ".ds 2" toInit :: A.Type -> A.Expr -> String toInit (A.Type t) (A.Num v _) | t == "bool" || t == "u8" || t == "s8" = ".db " ++ show v | t == "u16" || t == "s16" = ".dw " ++ show v | otherwise = ".dw " ++ show v toInit _ v = ".dw " ++ show v header :: String -> [String] header version = [";", "; File created by Micro v" ++ version ++ " (SDCC)", ";"] module' :: String -> String module' name = "\t.module " ++ name optsdcc :: String optsdcc = "\t.optsdcc -mz80" area :: String -> String area name = "\n\t.area " ++ name globl :: String -> String globl id = "\t.globl " ++ id data Output = Output { oPre :: [String], oInit :: [String], oData :: [String], oCode :: [String] } emit :: A.Expr -> Output emit x = case x of (A.Module name _) -> o {oPre = [module' name, optsdcc, ""]} (A.Var id typ val priv False _) -> o { oPre = if priv then [] else [globl $ toIdent id], oData = [toLabel id priv, "\t" ++ toData typ], oInit = ["__init" ++ toLabel id True, "\t" ++ toInit typ val] } (A.Num v _) -> o {oCode = ["\tld a, #" ++ show v]} (A.Variable id _) -> o {oCode = ["\tld a, (" ++ toIdent id ++ ")"]} -- cases where constant folding didn't happen (A.BinOp A.Plus _ (A.Num a _) (A.Num b _)) -> o {oCode = [show a ++ "+" ++ show b]} (A.BinOp A.Minus _ (A.Num a _) (A.Num b _)) -> o {oCode = [show a ++ "-" ++ show b]} (A.BinOp A.Mul _ (A.Num a _) (A.Num b _)) -> o {oCode = [show a ++ "*" ++ show b]} (A.BinOp A.Div _ (A.Num a _) (A.Num b _)) -> o {oCode = [show a ++ "/" ++ show b]} (A.BinOp A.Plus _ a (A.Num 1 _)) -> o {oCode = oCode (emit a) ++ ["\tinc a"]} (A.BinOp A.Plus _ a@(A.Variable _ _) (A.Num v _)) -> o {oCode = oCode (emit a) ++ ["\tadd #" ++ show v]} (A.BinOp A.Plus _ a b) -> o {oCode = oCode (emit a) ++ ["\tld c, a"] ++ oCode (emit b) ++ ["\tadd c"]} (A.BinOp A.Minus _ a (A.Num 1 _)) -> o {oCode = oCode (emit a) ++ ["\tdec a"]} (A.BinOp A.Minus _ a@(A.Variable _ _) (A.Num v _)) -> o {oCode = oCode (emit a) ++ ["\tsub #" ++ show v]} (A.BinOp A.Minus _ a b) -> o {oCode = oCode (emit a) ++ ["\tld c, a"] ++ oCode (emit b) ++ ["\tsub c"]} (A.BinOp A.Assign _ (A.Variable id _) b) -> o {oCode = oCode (emit b) ++ ["\tld (" ++ toIdent id ++ "), a"]} _ -> o {oCode = [";; unimplemented " ++ show x]} where o = Output [] [] [] [] generate :: String -> [A.Expr] -> String generate version ast = do out <- pure $ map emit ast pre <- pure $ concat $ map oPre out dat <- pure $ [area "_DATA", area "_INITIALIZED"] ++ concat (map oData out) code <- pure $ [area "_CODE"] ++ concat (map oCode out) ++ ["hlt0:", "\tjr hlt0"] init <- pure $ [area "_INITIALIZER"] ++ concat (map oInit out) ++ [area "_GSINIT", area "_GSFINAL"] unlines $ header version ++ pre ++ dat ++ code ++ init