Skip to content

Commit

Permalink
generate the main expression if not in the library mode
Browse files Browse the repository at this point in the history
  • Loading branch information
ulysses4ever committed Jun 20, 2024
1 parent 3c736d0 commit 2db208c
Show file tree
Hide file tree
Showing 3 changed files with 14 additions and 12 deletions.
9 changes: 9 additions & 0 deletions gibbon-compiler/src/Gibbon/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,7 @@ module Gibbon.Common
-- * Gibbon configuration
, Config(..), Input(..), Mode(..), Backend(..), defaultConfig
, RunConfig(..), getRunConfig, defaultRunConfig, getGibbonConfig
, isBench, isLibrary

-- * Misc helpers
, SSModality(..), (#), (!!!), fragileZip, fragileZip', sdoc, ndoc, abbrv
Expand Down Expand Up @@ -255,6 +256,14 @@ data Mode = ToParse -- ^ Parse and then stop
| Library Var -- ^ Compile as a library, with its main entry point given.
deriving (Show, Read, Eq, Ord)

isBench :: Mode -> Bool
isBench (Bench _) = True
isBench _ = False

isLibrary :: Mode -> Bool
isLibrary (Library _) = True
isLibrary _ = False

-- | Compilation backend used
data Backend = C | LLVM
deriving (Show,Read,Eq,Ord)
Expand Down
9 changes: 0 additions & 9 deletions gibbon-compiler/src/Gibbon/Compiler.hs
Original file line number Diff line number Diff line change
Expand Up @@ -542,15 +542,6 @@ compilationCmd C config = (cc config) ++" -std=gnu11 "
simpleWriteBarrier = gopt Opt_SimpleWriteBarrier dflags
lazyPromote = gopt Opt_NoEagerPromote dflags

-- |
isBench :: Mode -> Bool
isBench (Bench _) = True
isBench _ = False

isLibrary :: Mode -> Bool
isLibrary (Library _) = True
isLibrary _ = False

-- | The debug level at which we start to call the interpreter on the program during compilation.
interpDbgLevel :: Int
interpDbgLevel = 5
Expand Down
8 changes: 5 additions & 3 deletions gibbon-compiler/src/Gibbon/Passes/Codegen.hs
Original file line number Diff line number Diff line change
Expand Up @@ -189,7 +189,7 @@ sortFns (Prog _ _ funs mtal) = foldl go S.empty allTails
-- | Compile a program to C code that has the side effect of the
-- "gibbon_main" expression in that program.
codegenProg :: Config -> Prog -> IO String
codegenProg cfg prg@(Prog info_tbl sym_tbl funs mtal) =
codegenProg cfg@Config{mode} prg@(Prog info_tbl sym_tbl funs mtal) =
return (hashIncludes ++ pretty 80 (stack (map ppr defs)))
where
init_fun_env = foldr (\fn acc -> M.insert (funName fn) (map snd (funArgs fn), funRetTy fn) acc) M.empty funs
Expand All @@ -200,9 +200,11 @@ codegenProg cfg prg@(Prog info_tbl sym_tbl funs mtal) =
(prots,funs') <- (unzip . concat) <$> mapM codegenFun funs
main_expr' <- main_expr
let struct_tys = uniqueDicts $ S.toList $ harvestStructTys prg
return ((L.nub $ makeStructs struct_tys) ++ prots ++
return ((L.nub $ makeStructs struct_tys) ++
prots ++
[gibTypesEnum, initInfoTable info_tbl, initSymTable sym_tbl] ++
funs' -- ++ [main_expr']
funs' ++
if isLibrary mode then [] else [main_expr']
)

main_expr :: PassM C.Definition
Expand Down

0 comments on commit 2db208c

Please sign in to comment.