Skip to content

Commit dd4b6d7

Browse files
committed
L4.Tail: add EndOfMain marker; fix codegen to not generate two returns
We already always add a printing statement to the main expression, so the main expression is already special. Now we have a dedicated marker for the end of main, so that we can add some more specialty in the codegen. In particular, we don't generate a return statement for main in the generic codegen pass (`codegenTail`). Instead, a shutdown code for the whole program is generated elsewhere. This has been done before, but the main pass generated an extra return for main (because it looked like a regular function) and the shutdown code was never executed. The new special marker allows to tell between a regular function and main, and to skip the return statement in the latter case. Fix #242
1 parent 64f0447 commit dd4b6d7

File tree

5 files changed

+12
-1
lines changed

5 files changed

+12
-1
lines changed

gibbon-compiler/src/Gibbon/L4/Syntax.hs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -117,6 +117,9 @@ data DataConInfo = DataConInfo
117117

118118
data Tail
119119
= RetValsT [Triv] -- ^ Only in tail position, for returning from a function.
120+
121+
| EndOfMain -- ^ A marker for an end of the main expression.
122+
120123
| AssnValsT { upd :: [(Var,Ty,Triv)]
121124
, bod_maybe :: Maybe Tail
122125
}
@@ -397,6 +400,7 @@ withTail (tl0,retty) fn =
397400
let go x = withTail (x,retty) fn in -- Warning: assumes same type.
398401
case tl0 of
399402
Goto{} -> return tl0
403+
EndOfMain{} -> return tl0
400404
RetValsT ls -> return $ fn ls
401405
(ErrT x) -> return $ ErrT x
402406
(AssnValsT _ _) -> error $ "withTail: expected tail expression returning values, not: "++show tl0
@@ -455,6 +459,7 @@ inlineTrivL4 (Prog info_tbl sym_tbl fundefs mb_main) =
455459
inline_tail :: M.Map Var Triv -> Tail -> Tail
456460
inline_tail env tl =
457461
case tl of
462+
EndOfMain -> tl
458463
RetValsT trvs -> RetValsT (map (inline env) trvs)
459464
AssnValsT assns mb_bod -> AssnValsT
460465
(map (\(v,ty,trv) -> (v,ty,inline env trv)) assns)

gibbon-compiler/src/Gibbon/Passes/Codegen.hs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -78,6 +78,7 @@ harvestStructTys (Prog _ _ funs mtal) =
7878
where
7979
go tl =
8080
case tl of
81+
EndOfMain -> []
8182
(RetValsT _) -> []
8283
(AssnValsT ls bod_maybe) ->
8384
case bod_maybe of
@@ -146,6 +147,7 @@ sortFns (Prog _ _ funs mtal) = foldl go S.empty allTails
146147

147148
go acc tl =
148149
case tl of
150+
EndOfMain -> acc
149151
RetValsT{} -> acc
150152
AssnValsT _ mb_bod -> case mb_bod of
151153
Just bod -> go acc bod
@@ -421,6 +423,7 @@ rewriteReturns :: Tail -> [(Var,Ty)] -> Tail
421423
rewriteReturns tl bnds =
422424
let go x = rewriteReturns x bnds in
423425
case tl of
426+
EndOfMain -> tl
424427
(RetValsT ls) -> AssnValsT [ (v,t,e) | (v,t) <- bnds | e <- ls ] Nothing
425428
(Goto _) -> tl
426429

@@ -504,6 +507,7 @@ ssDecls =
504507
-- | The central codegen function.
505508
codegenTail :: VEnv -> FEnv -> S.Set Var -> Tail -> Ty -> SyncDeps -> PassM [C.BlockItem]
506509

510+
codegenTail _ _ _ EndOfMain _ty _ = return []
507511
-- Void type:
508512
codegenTail _ _ _ (RetValsT []) _ty _ = return [ C.BlockStm [cstm| return 0; |] ]
509513
-- Single return:

gibbon-compiler/src/Gibbon/Passes/Lower.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -324,7 +324,7 @@ addPrintToTail ty tl0 = do
324324
-- Always print a trailing newline at the end of execution:
325325
T.LetPrimCallT [] (T.PrintString "\n") [] $
326326
-- T.LetPrimCallT [] T.FreeSymTable [] $
327-
T.RetValsT [] -- Void return after printing.
327+
T.EndOfMain -- marker of the end of main expression
328328

329329
-- | Look up the numeric tag for a dataCon
330330
getTagOfDataCon :: Out a => DDefs a -> DataCon -> Tag

gibbon-compiler/src/Gibbon/Passes/RearrangeFree.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -26,6 +26,7 @@ rearrangeFreeFn f@FunDecl{funBody} = do
2626
rearrangeFreeExp :: Bool -> Maybe (Tail -> Tail) -> Tail -> PassM Tail
2727
rearrangeFreeExp is_main frees tail =
2828
case tail of
29+
EndOfMain -> return tail
2930
LetPrimCallT binds prim rands bod ->
3031
case prim of
3132
FreeBuffer -> do

gibbon-compiler/src/Gibbon/Passes/Simplifier.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -246,6 +246,7 @@ lateInlineTriv (L4.Prog info_tbl sym_tbl fundefs mainExp) = do
246246
L4.IntAlts ls -> L4.IntAlts $ map (\(t,tl) -> (t,go env tl)) ls
247247
go env tl =
248248
case tl of
249+
L4.EndOfMain -> L4.EndOfMain
249250
L4.RetValsT trvs ->
250251
L4.RetValsT (map (gotriv env) trvs)
251252
L4.AssnValsT upd mb_bod ->

0 commit comments

Comments
 (0)