aboutsummaryrefslogtreecommitdiff
path: root/src/Micro/Asm/Sdcc.hs
diff options
context:
space:
mode:
authorJuan J. Martinez <jjm@usebox.net>2022-09-09 16:54:06 +0100
committerJuan J. Martinez <jjm@usebox.net>2022-09-09 16:54:06 +0100
commitbcc469bc7f1d73e66828637b5b518b7cab8e2781 (patch)
tree84d7a1d4a9b9c07797583c03b3fda274ee740148 /src/Micro/Asm/Sdcc.hs
parentcdf88f13008cd3f6511d466c1078ae7b2f983faf (diff)
downloadmicro-lang-hs-bcc469bc7f1d73e66828637b5b518b7cab8e2781.tar.gz
micro-lang-hs-bcc469bc7f1d73e66828637b5b518b7cab8e2781.zip
SDCC generation WIP
Diffstat (limited to 'src/Micro/Asm/Sdcc.hs')
-rw-r--r--src/Micro/Asm/Sdcc.hs63
1 files changed, 61 insertions, 2 deletions
diff --git a/src/Micro/Asm/Sdcc.hs b/src/Micro/Asm/Sdcc.hs
index 916fa3e..ef655d4 100644
--- a/src/Micro/Asm/Sdcc.hs
+++ b/src/Micro/Asm/Sdcc.hs
@@ -1,7 +1,66 @@
module Micro.Asm.Sdcc where
+import qualified Data.Map as Map
import qualified Micro.Ast as A
-import Micro.Env (SymMap)
+import Micro.Env (Sym (..), SymMap)
+
+toIdent :: A.Ident -> Bool -> String
+toIdent id False = "_" ++ id
+toIdent id True = id
+
+toLabel :: A.Ident -> Bool -> String
+toLabel id False = toIdent id False ++ "::"
+toLabel id True = 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 -> String
+toInit (A.Type t)
+ | t == "bool" || t == "u8" || t == "s8" = ".db"
+ | t == "u16" || t == "s16" = ".dw"
+ | otherwise = ".dw"
+toInit (A.FuncType _ _) = ".dw"
+
+onlyData :: SymMap -> [Sym]
+onlyData symm =
+ filter (\sym -> symRef sym) $
+ Map.elems symm
+
+header :: [String]
+header = [";", "; File created by $$$ v?.?.? (SDCC)", ";"]
+
+module' :: A.Expr -> [String]
+module' (A.Module name _) = ["\t.module " ++ name, "\t.optsdcc -mz80"]
+module' _ = ["\t.module main"] -- won't happen
+
+exports :: SymMap -> [String]
+exports symm =
+ [""]
+ ++ ( map (\sym -> "\t.globl " ++ toIdent (symId sym) False) $
+ Map.elems $ Map.filter (\sym -> not $ symPriv sym) symm
+ )
+
+dataVars :: SymMap -> [String]
+dataVars symm =
+ ["\n\t.area _DATA", "\t.area _INITIALIZED"]
+ ++ ( map (\sym -> toLabel (symId sym) (symPriv sym) ++ "\n\t" ++ toData (symType sym)) $
+ onlyData symm
+ )
+
+initVars :: SymMap -> [String]
+initVars symm =
+ ["\n\t.area _INITIALIZER"]
+ ++ ( map (\sym -> "__xinit_" ++ toLabel (symId sym) True ++ "\n\t" ++ toInit (symType sym) ++ " FIXME") $ onlyData symm
+ )
+ ++ ["\n\t.area _GSINIT", "\t.area _GSFINAL"]
+
+code :: [String]
+code = ["\n\t.area _CODE"]
generate :: SymMap -> [A.Expr] -> String
-generate sym ast = "OUTPUT"
+generate symm ast = unlines $ header ++ module' (head ast) ++ exports symm ++ dataVars symm ++ code ++ initVars symm