Skip to content

Commit

Permalink
cleanup transformation
Browse files Browse the repository at this point in the history
  • Loading branch information
lukaszcz committed Feb 20, 2024
1 parent cb808c1 commit 639e650
Show file tree
Hide file tree
Showing 6 changed files with 43 additions and 6 deletions.
5 changes: 3 additions & 2 deletions src/Juvix/Compiler/Pipeline.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ import Juvix.Compiler.Pipeline.Package.Loader.Error
import Juvix.Compiler.Pipeline.Package.Loader.EvalEff
import Juvix.Compiler.Pipeline.Result
import Juvix.Compiler.Pipeline.Root.Base
import Juvix.Compiler.Reg.Data.InfoTable qualified as Reg
import Juvix.Compiler.Reg.Pipeline qualified as Reg
import Juvix.Compiler.Reg.Translation.FromAsm qualified as Reg
import Juvix.Compiler.Store.Language qualified as Store
import Juvix.Compiler.Tree qualified as Tree
Expand Down Expand Up @@ -202,8 +202,9 @@ asmToMiniC = asmToReg >=> regToMiniC

regToMiniC :: (Member (Reader EntryPoint) r) => Reg.InfoTable -> Sem r C.MiniCResult
regToMiniC tab = do
tab' <- Reg.toC tab
e <- ask
return $ C.fromReg (Backend.getLimits (e ^. entryPointTarget) (e ^. entryPointDebug)) tab
return $ C.fromReg (Backend.getLimits (e ^. entryPointTarget) (e ^. entryPointDebug)) tab'

treeToNockma' :: (Members '[Error JuvixError, Reader NockmaTree.CompilerOptions] r) => Tree.InfoTable -> Sem r (Nockma.Cell Natural)
treeToNockma' = Tree.toNockma >=> NockmaTree.fromTreeTable
Expand Down
10 changes: 6 additions & 4 deletions src/Juvix/Compiler/Reg/Data/TransformationId.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,26 +7,28 @@ import Juvix.Prelude
data TransformationId
= Identity
| SSA
| Cleanup
deriving stock (Data, Bounded, Enum, Show)

data PipelineId
= PipelineC
| PipelineCairo
= PipelineCairo
| PipelineC
deriving stock (Data, Bounded, Enum)

type TransformationLikeId = TransformationLikeId' TransformationId PipelineId

toCTransformations :: [TransformationId]
toCTransformations = []
toCTransformations = [Cleanup]

toCairoTransformations :: [TransformationId]
toCairoTransformations = [SSA]
toCairoTransformations = [Cleanup, SSA]

instance TransformationId' TransformationId where
transformationText :: TransformationId -> Text
transformationText = \case
Identity -> strIdentity
SSA -> strSSA
Cleanup -> strCleanup

instance PipelineId' TransformationId PipelineId where
pipelineText :: PipelineId -> Text
Expand Down
3 changes: 3 additions & 0 deletions src/Juvix/Compiler/Reg/Data/TransformationId/Strings.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,3 +13,6 @@ strIdentity = "identity"

strSSA :: Text
strSSA = "ssa"

strCleanup :: Text
strCleanup = "cleanup"
16 changes: 16 additions & 0 deletions src/Juvix/Compiler/Reg/Pipeline.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
module Juvix.Compiler.Reg.Pipeline
( module Juvix.Compiler.Reg.Pipeline,
module Juvix.Compiler.Reg.Data.InfoTable,
)
where

import Juvix.Compiler.Reg.Data.InfoTable
import Juvix.Compiler.Reg.Transformation

-- | Perform transformations on JuvixReg necessary before the translation to C
toC :: InfoTable -> Sem r InfoTable
toC = applyTransformations toCTransformations

-- | Perform transformations on JuvixReg necessary before the translation to Cairo
toCairo :: InfoTable -> Sem r InfoTable
toCairo = applyTransformations toCairoTransformations
2 changes: 2 additions & 0 deletions src/Juvix/Compiler/Reg/Transformation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@ where

import Juvix.Compiler.Reg.Data.TransformationId
import Juvix.Compiler.Reg.Transformation.Base
import Juvix.Compiler.Reg.Transformation.Cleanup
import Juvix.Compiler.Reg.Transformation.Identity
import Juvix.Compiler.Reg.Transformation.SSA

Expand All @@ -17,3 +18,4 @@ applyTransformations ts tbl = foldM (flip appTrans) tbl ts
appTrans = \case
Identity -> return . identity
SSA -> return . computeSSA
Cleanup -> return . cleanup
13 changes: 13 additions & 0 deletions src/Juvix/Compiler/Reg/Transformation/Cleanup.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
module Juvix.Compiler.Reg.Transformation.Cleanup where

import Juvix.Compiler.Reg.Extra.Recursors
import Juvix.Compiler.Reg.Transformation.Base

cleanup :: InfoTable -> InfoTable
cleanup = mapT (const (cmap go))
where
go :: Code -> Code
go = \case
Nop : is -> is
Block InstrBlock {..} : is -> _instrBlockCode ++ is
is -> is

0 comments on commit 639e650

Please sign in to comment.