aboutsummaryrefslogtreecommitdiff
path: root/Sil
diff options
context:
space:
mode:
authorCamil Staps2017-07-28 23:46:38 +0200
committerCamil Staps2017-07-28 23:46:38 +0200
commitfe76e2ad510ec9e4df965a9620f8d36778222c08 (patch)
tree4caec2a73064dc9ed44214c9625c99cf379647b8 /Sil
parentAdd a semi-memoized fibonacci with lists (diff)
Add globals on A-stack
Diffstat (limited to 'Sil')
-rw-r--r--Sil/Check.dcl1
-rw-r--r--Sil/Check.icl9
-rw-r--r--Sil/Compile.icl37
-rw-r--r--Sil/Parse.icl6
-rw-r--r--Sil/Syntax.dcl3
-rw-r--r--Sil/Util/Printer.icl4
6 files changed, 47 insertions, 13 deletions
diff --git a/Sil/Check.dcl b/Sil/Check.dcl
index a34eb99..9eff566 100644
--- a/Sil/Check.dcl
+++ b/Sil/Check.dcl
@@ -15,6 +15,7 @@ from Sil.Types import :: Type
| ReturnExpressionFromVoid Name
| NoReturnFromNonVoid Name
| LocalVoid Name Name
+ | BasicGlobal Name
instance toString CheckError
diff --git a/Sil/Check.icl b/Sil/Check.icl
index c51d73c..f9147bf 100644
--- a/Sil/Check.icl
+++ b/Sil/Check.icl
@@ -34,6 +34,8 @@ where
= "Type error: no return from non-void function '" <+ f <+ "'."
toString (LocalVoid f l)
= "Type error: local variable '" <+ l <+ "' in '" <+ f <+ "' cannot have type Void."
+ toString (BasicGlobal g)
+ = "Error: global variable '" <+ g <+ "' cannot have a basic type."
instance <<< CheckError where <<< f e = f <<< toString e <<< "\r\n"
@@ -42,6 +44,7 @@ checkProgram err prog
= checkErrors
[ checkFunctionNames
, checkMainFunction
+ , checkGlobals
] prog
$ appFst flatten $ mapSt (flip checkFunction) prog.p_funs err
where
@@ -56,6 +59,12 @@ where
\\ fs <- tails [f.f_name \\ f <- p.p_funs]
| not (isEmpty fs) && isMember (hd fs) (tl fs)]
+ checkGlobals :: Program -> [CheckError]
+ checkGlobals p =
+ [ BasicGlobal g.init_name
+ \\ g <- p.p_globals
+ | (typeSize g.init_type).bsize <> 0]
+
checkFunction :: *(Maybe *File) Function -> *([CheckError], *Maybe *File)
checkFunction err f = checkErrors
[ checkLocals
diff --git a/Sil/Compile.icl b/Sil/Compile.icl
index 9404b1c..0d5a3f2 100644
--- a/Sil/Compile.icl
+++ b/Sil/Compile.icl
@@ -98,6 +98,7 @@ where
, returns :: ['ABC'.Assembler]
, returnType :: Type
, stackoffsets :: (Int, Int) // A and B stack
+ , globalsize :: (Int, Int)
, storedoffsets :: [(Int, Int)]
, typeresolvers :: [TypeResolver]
}
@@ -111,6 +112,7 @@ where
, returns = []
, returnType = TVoid
, stackoffsets = (0, 0)
+ , globalsize = (0, 0)
, storedoffsets = []
, typeresolvers = []
}
@@ -133,6 +135,9 @@ returnType cs = cs.returnType
stackoffsets :: CompileState -> (Int, Int)
stackoffsets cs = cs.stackoffsets
+globalsize :: CompileState -> (Int, Int)
+globalsize cs = cs.globalsize
+
typeresolvers :: CompileState -> [TypeResolver]
typeresolvers cs = cs.typeresolvers
@@ -259,14 +264,21 @@ instance gen Program
where
gen p =
tell [ 'ABC'.Annotation $ 'ABC'.RawAnnot ["comp", "920", "01011101001"]
- , 'ABC'.Annotation $ 'ABC'.RawAnnot ["start", "__sil_boot"]
+ , 'ABC'.Annotation $ 'ABC'.RawAnnot ["start", "_sil_boot"]
, 'ABC'.Annotation $ 'ABC'.RawAnnot ["endinfo"]
, 'ABC'.Annotation $ 'ABC'.RawAnnot ["module", "m_sil_compiled", "\"sil_compiled\""]
- , 'ABC'.Label "__sil_boot"
+ , 'ABC'.Label "_sil_boot"
, 'ABC'.Create
- , 'ABC'.Fill "_" 0 (toLabel "main") 0
+ , 'ABC'.Fill "_" 0 "_sil_boot2" 0
, 'ABC'.Jmp "_driver"
- ] *>
+ , 'ABC'.Annotation $ 'ABC'.OAnnot 0 []
+ , 'ABC'.Label "_sil_boot2" ] *>
+ let gsize = foldr (+~) zero [typeSize i.init_type \\ i <- p.p_globals] in
+ modify (\cs -> {cs & globalsize=(gsize.asize, gsize.bsize)}) *>
+ shrinkStack gsize *>
+ mapM_ reserveVar [(i.init_name, i.init_type) \\ i <- p.p_globals] *>
+ mapM_ gen p.p_globals *>
+ tell [ 'ABC'.Jmp (toLabel "main") ] *>
pushTypeResolver typeresolver *>
mapM_ addFunction p.p_funs *>
mapM_ gen p.p_funs *>
@@ -274,13 +286,18 @@ where
where
typeresolver :: Name -> Maybe (MaybeError Error Type)
typeresolver n = case [f \\ f <- p.p_funs | f.f_name == n] of
- [] -> Nothing
- [f:_] -> type zero f
+ [f:_] -> type typeresolver f
+ [] -> case [g.init_type \\ g <- p.p_globals | g.init_name == n] of
+ [t:_] -> Just $ Ok t
+ [] -> Nothing
instance gen Function
where
gen f =
- tell [ 'ABC'.Annotation $ toOAnnot` [typeSize a.arg_type \\ a <- f.f_args]
+ gets globalsize >>= \(gas,gbs) ->
+ tell [ 'ABC'.Annotation $ toOAnnot`
+ [if (f.f_name == "main") {zero & asize=gas,bsize=gbs} zero
+ :[typeSize a.arg_type \\ a <- f.f_args]]
, 'ABC'.Label $ toLabel f.f_name
] *>
tell (repeatn retSize.asize 'ABC'.Create) *>
@@ -371,10 +388,12 @@ where
instance gen Initialisation
where
gen init = case typeSize init.init_type of
- s=:{bsize=0} -> tell $ repeatn s.asize 'ABC'.Create
+ s=:{bsize=0} -> case init.init_value of
+ Nothing -> tell $ repeatn s.asize 'ABC'.Create
+ Just v -> shrinkStack s *> gen v
s=:{asize=0} -> case init.init_value of
Nothing -> error $ C_BasicInitWithoutValue init.init_name
- Just v -> checkType init.init_type v *> gen v *> shrinkStack s
+ Just v -> checkType init.init_type v *> shrinkStack s *> gen v
instance gen Statement
where
diff --git a/Sil/Parse.icl b/Sil/Parse.icl
index cdd117f..7325826 100644
--- a/Sil/Parse.icl
+++ b/Sil/Parse.icl
@@ -121,7 +121,11 @@ parse :: ([Token] -> MaybeError Error Program)
parse = fst o runParser program
program :: Parser Token Program
-program = (\fs -> {p_funs=fs}) <$> some function <* eof
+program =
+ many initialisation >>= \globss ->
+ some function >>= \fs ->
+ eof $>
+ {p_globals=flatten globss, p_funs=fs}
function :: Parser Token Function
function =
diff --git a/Sil/Syntax.dcl b/Sil/Syntax.dcl
index e3a458d..c76eb13 100644
--- a/Sil/Syntax.dcl
+++ b/Sil/Syntax.dcl
@@ -7,7 +7,8 @@ from Data.Maybe import :: Maybe
from Sil.Types import :: Type
:: Program =
- { p_funs :: [Function]
+ { p_funs :: [Function]
+ , p_globals :: [Initialisation]
}
:: Function =
diff --git a/Sil/Util/Printer.icl b/Sil/Util/Printer.icl
index 3ed15fb..55c2498 100644
--- a/Sil/Util/Printer.icl
+++ b/Sil/Util/Printer.icl
@@ -68,9 +68,9 @@ where
instance PrettyPrinter Program
where
- print st prog = p st prog.p_funs
+ print st prog = p st prog.p_globals <+ "\r\n" <+ p st prog.p_funs
where
- p :: PrintState [Function] -> String
+ p :: PrintState [a] -> String | PrettyPrinter a
p _ [] = ""
p st [f] = print st f
p st [f:fs] = print st f <+ "\r\n\r\n" <+ p st fs