Skip to content

Commit

Permalink
Add pass to compiler pipeline
Browse files Browse the repository at this point in the history
  • Loading branch information
jazullo committed Jan 10, 2024
1 parent 35b5913 commit 403b5e7
Show file tree
Hide file tree
Showing 3 changed files with 10 additions and 3 deletions.
1 change: 1 addition & 0 deletions gibbon-compiler/gibbon.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,7 @@ library

Gibbon.L0.Syntax
Gibbon.L0.Typecheck
Gibbon.L0.ElimNewtype
Gibbon.L0.Specialize2
Gibbon.L0.Interp
Gibbon.L1.Syntax
Expand Down
3 changes: 3 additions & 0 deletions gibbon-compiler/src/Gibbon/Compiler.hs
Original file line number Diff line number Diff line change
Expand Up @@ -56,6 +56,7 @@ import Gibbon.L2.Interp ( Store, emptyStore )
-- Compiler passes
import qualified Gibbon.L0.Typecheck as L0
import qualified Gibbon.L0.Specialize2 as L0
import qualified Gibbon.L0.ElimNewtype as L0
import qualified Gibbon.L1.Typecheck as L1
import qualified Gibbon.L2.Typecheck as L2
import qualified Gibbon.L3.Typecheck as L3
Expand Down Expand Up @@ -642,6 +643,8 @@ passes config@Config{dynflags} l0 = do
tcProg3 = L3.tcProg isPacked
l0 <- go "freshen" freshNames l0
l0 <- goE0 "typecheck" L0.tcProg l0
l0 <- go "elimNewtypes" L0.elimNewtypes l0
l0 <- goE0 "typecheck" L0.tcProg l0
l0 <- goE0 "bindLambdas" L0.bindLambdas l0
l0 <- goE0 "monomorphize" L0.monomorphize l0
-- l0 <- goE0 "closureConvert" L0.closureConvert l0
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Gibbon.Passes.ElimNewtype where
module Gibbon.L0.ElimNewtype where

import Gibbon.L0.Syntax
import Gibbon.Common
Expand All @@ -9,8 +9,11 @@ import qualified Data.Set as S
import Data.Maybe ( fromMaybe )
import Data.Symbol ( unintern )

passProgram :: Prog0 -> Prog0
passProgram prog =
elimNewtypes :: Monad m => Prog0 -> m Prog0
elimNewtypes = pure . elimProgram

elimProgram :: Prog0 -> Prog0
elimProgram prog =
Prog
{ mainExp = (elimE connames tynames (ddefs prog) *** elimTy tynames) <$> mainExp prog
, fundefs = fdefs
Expand Down

0 comments on commit 403b5e7

Please sign in to comment.