summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSylvain Henry <sylvain@haskus.fr>2020-01-07 01:44:39 (GMT)
committerMarge Bot <ben+marge-bot@smart-cactus.org>2020-01-25 10:22:20 (GMT)
commit6e2d9ee25bce06ae51d2f1cf8df4f7422106a383 (patch)
tree4bb0aa9527bc0bed4fb2e991eb02d0f031d514bf
parentc3fde723633d1788e4ded8c6f59eb7cef1ae95fd (diff)
downloadghc-6e2d9ee25bce06ae51d2f1cf8df4f7422106a383.zip
ghc-6e2d9ee25bce06ae51d2f1cf8df4f7422106a383.tar.gz
ghc-6e2d9ee25bce06ae51d2f1cf8df4f7422106a383.tar.bz2
Module hierarchy: Cmm (cf #13009)
-rw-r--r--aclocal.m42
-rw-r--r--compiler/GHC/Cmm.hs (renamed from compiler/cmm/Cmm.hs)30
-rw-r--r--compiler/GHC/Cmm/BlockId.hs (renamed from compiler/cmm/BlockId.hs)6
-rw-r--r--compiler/GHC/Cmm/BlockId.hs-boot8
-rw-r--r--compiler/GHC/Cmm/CLabel.hs (renamed from compiler/cmm/CLabel.hs)6
-rw-r--r--compiler/GHC/Cmm/CallConv.hs (renamed from compiler/cmm/CmmCallConv.hs)10
-rw-r--r--compiler/GHC/Cmm/CommonBlockElim.hs (renamed from compiler/cmm/CmmCommonBlockElim.hs)20
-rw-r--r--compiler/GHC/Cmm/ContFlowOpt.hs (renamed from compiler/cmm/CmmContFlowOpt.hs)18
-rw-r--r--compiler/GHC/Cmm/Dataflow.hs (renamed from compiler/cmm/Hoopl/Dataflow.hs)12
-rw-r--r--compiler/GHC/Cmm/Dataflow/Block.hs (renamed from compiler/cmm/Hoopl/Block.hs)2
-rw-r--r--compiler/GHC/Cmm/Dataflow/Collections.hs (renamed from compiler/cmm/Hoopl/Collections.hs)2
-rw-r--r--compiler/GHC/Cmm/Dataflow/Graph.hs (renamed from compiler/cmm/Hoopl/Graph.hs)8
-rw-r--r--compiler/GHC/Cmm/Dataflow/Label.hs (renamed from compiler/cmm/Hoopl/Label.hs)4
-rw-r--r--compiler/GHC/Cmm/DebugBlock.hs (renamed from compiler/cmm/Debug.hs)24
-rw-r--r--compiler/GHC/Cmm/Expr.hs (renamed from compiler/cmm/CmmExpr.hs)20
-rw-r--r--compiler/GHC/Cmm/Graph.hs (renamed from compiler/cmm/MkGraph.hs)18
-rw-r--r--compiler/GHC/Cmm/Info.hs (renamed from compiler/cmm/CmmInfo.hs)16
-rw-r--r--compiler/GHC/Cmm/Info/Build.hs (renamed from compiler/cmm/CmmBuildInfoTables.hs)22
-rw-r--r--compiler/GHC/Cmm/LayoutStack.hs (renamed from compiler/cmm/CmmLayoutStack.hs)30
-rw-r--r--compiler/GHC/Cmm/Lexer.x (renamed from compiler/cmm/CmmLex.x)6
-rw-r--r--compiler/GHC/Cmm/Lint.hs (renamed from compiler/cmm/CmmLint.hs)22
-rw-r--r--compiler/GHC/Cmm/Liveness.hs (renamed from compiler/cmm/CmmLive.hs)16
-rw-r--r--compiler/GHC/Cmm/MachOp.hs (renamed from compiler/cmm/CmmMachOp.hs)4
-rw-r--r--compiler/GHC/Cmm/Monad.hs (renamed from compiler/cmm/CmmMonad.hs)2
-rw-r--r--compiler/GHC/Cmm/Node.hs (renamed from compiler/cmm/CmmNode.hs)26
-rw-r--r--compiler/GHC/Cmm/Opt.hs (renamed from compiler/cmm/CmmOpt.hs)6
-rw-r--r--compiler/GHC/Cmm/Parser.y (renamed from compiler/cmm/CmmParse.y)30
-rw-r--r--compiler/GHC/Cmm/Pipeline.hs (renamed from compiler/cmm/CmmPipeline.hs)22
-rw-r--r--compiler/GHC/Cmm/Ppr.hs (renamed from compiler/cmm/PprCmm.hs)22
-rw-r--r--compiler/GHC/Cmm/Ppr/Decl.hs (renamed from compiler/cmm/PprCmmDecl.hs)6
-rw-r--r--compiler/GHC/Cmm/Ppr/Expr.hs (renamed from compiler/cmm/PprCmmExpr.hs)8
-rw-r--r--compiler/GHC/Cmm/ProcPoint.hs (renamed from compiler/cmm/CmmProcPoint.hs)30
-rw-r--r--compiler/GHC/Cmm/Sink.hs (renamed from compiler/cmm/CmmSink.hs)20
-rw-r--r--compiler/GHC/Cmm/Switch.hs (renamed from compiler/cmm/CmmSwitch.hs)46
-rw-r--r--compiler/GHC/Cmm/Switch/Implement.hs (renamed from compiler/cmm/CmmImplementSwitchPlans.hs)18
-rw-r--r--compiler/GHC/Cmm/Type.hs (renamed from compiler/cmm/CmmType.hs)2
-rw-r--r--compiler/GHC/Cmm/Utils.hs (renamed from compiler/cmm/CmmUtils.hs)18
-rw-r--r--compiler/GHC/Cmm/cmm-notes (renamed from compiler/cmm/cmm-notes)4
-rw-r--r--compiler/GHC/CmmToC.hs (renamed from compiler/cmm/PprC.hs)20
-rw-r--r--compiler/GHC/Data/Bitmap.hs (renamed from compiler/cmm/Bitmap.hs)6
-rw-r--r--compiler/GHC/Platform/Regs.hs2
-rw-r--r--compiler/GHC/Runtime/Layout.hs (renamed from compiler/cmm/SMRep.hs)2
-rw-r--r--compiler/GHC/Stg/Lift/Analysis.hs2
-rw-r--r--compiler/GHC/StgToCmm.hs8
-rw-r--r--compiler/GHC/StgToCmm/ArgRep.hs2
-rw-r--r--compiler/GHC/StgToCmm/Bind.hs18
-rw-r--r--compiler/GHC/StgToCmm/CgUtils.hs10
-rw-r--r--compiler/GHC/StgToCmm/Closure.hs10
-rw-r--r--compiler/GHC/StgToCmm/DataCon.hs10
-rw-r--r--compiler/GHC/StgToCmm/Env.hs10
-rw-r--r--compiler/GHC/StgToCmm/Expr.hs8
-rw-r--r--compiler/GHC/StgToCmm/ExtCode.hs8
-rw-r--r--compiler/GHC/StgToCmm/Foreign.hs20
-rw-r--r--compiler/GHC/StgToCmm/Heap.hs16
-rw-r--r--compiler/GHC/StgToCmm/Hpc.hs8
-rw-r--r--compiler/GHC/StgToCmm/Layout.hs14
-rw-r--r--compiler/GHC/StgToCmm/Monad.hs18
-rw-r--r--compiler/GHC/StgToCmm/Prim.hs14
-rw-r--r--compiler/GHC/StgToCmm/Prof.hs10
-rw-r--r--compiler/GHC/StgToCmm/Ticky.hs16
-rw-r--r--compiler/GHC/StgToCmm/Utils.hs20
-rw-r--r--compiler/basicTypes/Unique.hs2
-rw-r--r--compiler/cmm/BlockId.hs-boot8
-rw-r--r--compiler/deSugar/Coverage.hs2
-rw-r--r--compiler/deSugar/DsForeign.hs4
-rw-r--r--compiler/ghc.cabal.in76
-rw-r--r--compiler/ghci/ByteCodeAsm.hs2
-rw-r--r--compiler/ghci/ByteCodeGen.hs4
-rw-r--r--compiler/ghci/ByteCodeInstr.hs2
-rw-r--r--compiler/ghci/RtClosureInspect.hs2
-rw-r--r--compiler/llvmGen/LlvmCodeGen.hs6
-rw-r--r--compiler/llvmGen/LlvmCodeGen/Base.hs6
-rw-r--r--compiler/llvmGen/LlvmCodeGen/CodeGen.hs18
-rw-r--r--compiler/llvmGen/LlvmCodeGen/Data.hs6
-rw-r--r--compiler/llvmGen/LlvmCodeGen/Ppr.hs4
-rw-r--r--compiler/llvmGen/LlvmCodeGen/Regs.hs2
-rw-r--r--compiler/main/CodeOutput.hs6
-rw-r--r--compiler/main/Hooks.hs2
-rw-r--r--compiler/main/HscMain.hs10
-rw-r--r--compiler/main/StaticPtrTable.hs2
-rw-r--r--compiler/nativeGen/AsmCodeGen.hs22
-rw-r--r--compiler/nativeGen/BlockLayout.hs10
-rw-r--r--compiler/nativeGen/CFG.hs25
-rw-r--r--compiler/nativeGen/CPrim.hs4
-rw-r--r--compiler/nativeGen/Dwarf.hs10
-rw-r--r--compiler/nativeGen/Dwarf/Types.hs6
-rw-r--r--compiler/nativeGen/Format.hs2
-rw-r--r--compiler/nativeGen/Instruction.hs8
-rw-r--r--compiler/nativeGen/NCGMonad.hs12
-rw-r--r--compiler/nativeGen/PIC.hs8
-rw-r--r--compiler/nativeGen/PPC/CodeGen.hs16
-rw-r--r--compiler/nativeGen/PPC/Instr.hs12
-rw-r--r--compiler/nativeGen/PPC/Ppr.hs12
-rw-r--r--compiler/nativeGen/PPC/RegInfo.hs6
-rw-r--r--compiler/nativeGen/PPC/Regs.hs4
-rw-r--r--compiler/nativeGen/PprBase.hs4
-rw-r--r--compiler/nativeGen/RegAlloc/Graph/Coalesce.hs2
-rw-r--r--compiler/nativeGen/RegAlloc/Graph/Spill.hs6
-rw-r--r--compiler/nativeGen/RegAlloc/Graph/SpillClean.hs6
-rw-r--r--compiler/nativeGen/RegAlloc/Graph/SpillCost.hs6
-rw-r--r--compiler/nativeGen/RegAlloc/Linear/Base.hs2
-rw-r--r--compiler/nativeGen/RegAlloc/Linear/JoinToTargets.hs4
-rw-r--r--compiler/nativeGen/RegAlloc/Linear/Main.hs8
-rw-r--r--compiler/nativeGen/RegAlloc/Linear/State.hs2
-rw-r--r--compiler/nativeGen/RegAlloc/Liveness.hs8
-rw-r--r--compiler/nativeGen/SPARC/CodeGen.hs14
-rw-r--r--compiler/nativeGen/SPARC/CodeGen/Amode.hs2
-rw-r--r--compiler/nativeGen/SPARC/CodeGen/Base.hs4
-rw-r--r--compiler/nativeGen/SPARC/CodeGen/CondCode.hs2
-rw-r--r--compiler/nativeGen/SPARC/CodeGen/Expand.hs2
-rw-r--r--compiler/nativeGen/SPARC/CodeGen/Gen32.hs2
-rw-r--r--compiler/nativeGen/SPARC/CodeGen/Gen32.hs-boot2
-rw-r--r--compiler/nativeGen/SPARC/CodeGen/Gen64.hs2
-rw-r--r--compiler/nativeGen/SPARC/CodeGen/Sanity.hs2
-rw-r--r--compiler/nativeGen/SPARC/Imm.hs4
-rw-r--r--compiler/nativeGen/SPARC/Instr.hs6
-rw-r--r--compiler/nativeGen/SPARC/Ppr.hs12
-rw-r--r--compiler/nativeGen/SPARC/ShortcutJump.hs6
-rw-r--r--compiler/nativeGen/X86/CodeGen.hs22
-rw-r--r--compiler/nativeGen/X86/Instr.hs12
-rw-r--r--compiler/nativeGen/X86/Ppr.hs10
-rw-r--r--compiler/nativeGen/X86/Regs.hs4
-rw-r--r--compiler/prelude/PrimOp.hs2
-rw-r--r--compiler/profiling/ProfInit.hs2
-rw-r--r--ghc.mk4
-rw-r--r--hadrian/src/Rules.hs4
-rw-r--r--hadrian/src/Rules/SourceDist.hs4
-rw-r--r--includes/Cmm.h4
-rw-r--r--includes/CodeGen.Platform.hs2
-rw-r--r--rts/Apply.cmm2
-rw-r--r--rts/Exception.cmm2
-rw-r--r--rts/HeapStackCheck.cmm2
-rw-r--r--rts/PrimOps.cmm2
-rw-r--r--rts/StgMiscClosures.cmm2
-rw-r--r--rts/StgStartup.cmm2
-rw-r--r--rts/StgStdThunks.cmm2
-rw-r--r--rts/Updates.cmm2
-rw-r--r--testsuite/tests/cmm/should_run/HooplPostorder.hs8
-rw-r--r--testsuite/tests/codeGen/should_run/T13825-unit.hs2
-rw-r--r--testsuite/tests/regalloc/regalloc_unit_tests.hs12
140 files changed, 678 insertions, 677 deletions
diff --git a/aclocal.m4 b/aclocal.m4
index 4a037a4..3dc30eb 100644
--- a/aclocal.m4
+++ b/aclocal.m4
@@ -999,7 +999,7 @@ else
fi;
changequote([, ])dnl
])
-if test ! -f compiler/parser/Parser.hs || test ! -f compiler/cmm/CmmParse.hs
+if test ! -f compiler/parser/Parser.hs || test ! -f compiler/GHC/Cmm/Parser.hs
then
FP_COMPARE_VERSIONS([$fptools_cv_happy_version],[-lt],[1.19.10],
[AC_MSG_ERROR([Happy version 1.19.10 or later is required to compile GHC.])])[]
diff --git a/compiler/cmm/Cmm.hs b/compiler/GHC/Cmm.hs
index e08b22f..5efecdc 100644
--- a/compiler/cmm/Cmm.hs
+++ b/compiler/GHC/Cmm.hs
@@ -1,7 +1,7 @@
-- Cmm representations using Hoopl's Graph CmmNode e x.
{-# LANGUAGE GADTs #-}
-module Cmm (
+module GHC.Cmm (
-- * Cmm top-level datatypes
CmmProgram, CmmGroup, GenCmmGroup,
CmmDecl, GenCmmDecl(..),
@@ -21,23 +21,23 @@ module Cmm (
ProfilingInfo(..), ConstrDescription,
-- * Statements, expressions and types
- module CmmNode,
- module CmmExpr,
+ module GHC.Cmm.Node,
+ module GHC.Cmm.Expr,
) where
import GhcPrelude
import Id
import CostCentre
-import CLabel
-import BlockId
-import CmmNode
-import SMRep
-import CmmExpr
-import Hoopl.Block
-import Hoopl.Collections
-import Hoopl.Graph
-import Hoopl.Label
+import GHC.Cmm.CLabel
+import GHC.Cmm.BlockId
+import GHC.Cmm.Node
+import GHC.Runtime.Layout
+import GHC.Cmm.Expr
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Dataflow.Graph
+import GHC.Cmm.Dataflow.Label
import Outputable
import Data.ByteString (ByteString)
@@ -126,7 +126,7 @@ data CmmStackInfo
-- used by the stack allocator later.
updfr_space :: Maybe ByteOff,
-- XXX: this never contains anything useful, but it should.
- -- See comment in CmmLayoutStack.
+ -- See comment in GHC.Cmm.LayoutStack.
do_layout :: Bool
-- Do automatic stack layout for this proc. This is
-- True for all code generated by the code generator,
@@ -149,13 +149,13 @@ data CmmInfoTable
-- the code generator, because we might want to add SRT
-- entries to them later (for FUNs at least; THUNKs are
-- treated the same for consistency). See Note [SRTs] in
- -- CmmBuildInfoTables, in particular the [FUN] optimisation.
+ -- GHC.Cmm.Info.Build, in particular the [FUN] optimisation.
--
-- This is strictly speaking not a part of the info table that
-- will be finally generated, but it's the only convenient
-- place to convey this information from the code generator to
-- where we build the static closures in
- -- CmmBuildInfoTables.doSRTs.
+ -- GHC.Cmm.Info.Build.doSRTs.
}
data ProfilingInfo
diff --git a/compiler/cmm/BlockId.hs b/compiler/GHC/Cmm/BlockId.hs
index 4f4e0e8..f7f3695 100644
--- a/compiler/cmm/BlockId.hs
+++ b/compiler/GHC/Cmm/BlockId.hs
@@ -2,7 +2,7 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}
{- BlockId module should probably go away completely, being superseded by Label -}
-module BlockId
+module GHC.Cmm.BlockId
( BlockId, mkBlockId -- ToDo: BlockId should be abstract, but it isn't yet
, newBlockId
, blockLbl, infoTblLbl
@@ -10,13 +10,13 @@ module BlockId
import GhcPrelude
-import CLabel
+import GHC.Cmm.CLabel
import IdInfo
import Name
import Unique
import UniqSupply
-import Hoopl.Label (Label, mkHooplLabel)
+import GHC.Cmm.Dataflow.Label (Label, mkHooplLabel)
----------------------------------------------------------------
--- Block Ids, their environments, and their sets
diff --git a/compiler/GHC/Cmm/BlockId.hs-boot b/compiler/GHC/Cmm/BlockId.hs-boot
new file mode 100644
index 0000000..76fd618
--- /dev/null
+++ b/compiler/GHC/Cmm/BlockId.hs-boot
@@ -0,0 +1,8 @@
+module GHC.Cmm.BlockId (BlockId, mkBlockId) where
+
+import GHC.Cmm.Dataflow.Label (Label)
+import Unique (Unique)
+
+type BlockId = Label
+
+mkBlockId :: Unique -> BlockId
diff --git a/compiler/cmm/CLabel.hs b/compiler/GHC/Cmm/CLabel.hs
index fb2f067..e84278b 100644
--- a/compiler/cmm/CLabel.hs
+++ b/compiler/GHC/Cmm/CLabel.hs
@@ -8,7 +8,7 @@
{-# LANGUAGE CPP #-}
-module CLabel (
+module GHC.Cmm.CLabel (
CLabel, -- abstract type
ForeignLabelSource(..),
pprDebugCLabel,
@@ -115,7 +115,7 @@ import GhcPrelude
import IdInfo
import BasicTypes
-import {-# SOURCE #-} BlockId (BlockId, mkBlockId)
+import {-# SOURCE #-} GHC.Cmm.BlockId (BlockId, mkBlockId)
import Packages
import Module
import Name
@@ -746,7 +746,7 @@ hasCAF _ = False
-- Until 14 Feb 2013, every ticky counter was associated with a
-- closure. Thus, ticky labels used IdLabel. It is odd that
--- CmmBuildInfoTables.cafTransfers would consider such a ticky label
+-- GHC.Cmm.Info.Build.cafTransfers would consider such a ticky label
-- reason to add the name to the CAFEnv (and thus eventually the SRT),
-- but it was harmless because the ticky was only used if the closure
-- was also.
diff --git a/compiler/cmm/CmmCallConv.hs b/compiler/GHC/Cmm/CallConv.hs
index df1eaad..9200dae 100644
--- a/compiler/cmm/CmmCallConv.hs
+++ b/compiler/GHC/Cmm/CallConv.hs
@@ -1,4 +1,4 @@
-module CmmCallConv (
+module GHC.Cmm.CallConv (
ParamLocation(..),
assignArgumentsPos,
assignStack,
@@ -7,10 +7,10 @@ module CmmCallConv (
import GhcPrelude
-import CmmExpr
-import SMRep
-import Cmm (Convention(..))
-import PprCmm () -- For Outputable instances
+import GHC.Cmm.Expr
+import GHC.Runtime.Layout
+import GHC.Cmm (Convention(..))
+import GHC.Cmm.Ppr () -- For Outputable instances
import DynFlags
import GHC.Platform
diff --git a/compiler/cmm/CmmCommonBlockElim.hs b/compiler/GHC/Cmm/CommonBlockElim.hs
index cbf7d83..86ea0e9 100644
--- a/compiler/cmm/CmmCommonBlockElim.hs
+++ b/compiler/GHC/Cmm/CommonBlockElim.hs
@@ -1,6 +1,6 @@
{-# LANGUAGE GADTs, BangPatterns, ScopedTypeVariables #-}
-module CmmCommonBlockElim
+module GHC.Cmm.CommonBlockElim
( elimCommonBlocks
)
where
@@ -8,16 +8,16 @@ where
import GhcPrelude hiding (iterate, succ, unzip, zip)
-import BlockId
-import Cmm
-import CmmUtils
-import CmmSwitch (eqSwitchTargetWith)
-import CmmContFlowOpt
+import GHC.Cmm.BlockId
+import GHC.Cmm
+import GHC.Cmm.Utils
+import GHC.Cmm.Switch (eqSwitchTargetWith)
+import GHC.Cmm.ContFlowOpt
-import Hoopl.Block
-import Hoopl.Graph
-import Hoopl.Label
-import Hoopl.Collections
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.Dataflow.Graph
+import GHC.Cmm.Dataflow.Label
+import GHC.Cmm.Dataflow.Collections
import Data.Bits
import Data.Maybe (mapMaybe)
import qualified Data.List as List
diff --git a/compiler/cmm/CmmContFlowOpt.hs b/compiler/GHC/Cmm/ContFlowOpt.hs
index 606da02..7765972 100644
--- a/compiler/cmm/CmmContFlowOpt.hs
+++ b/compiler/GHC/Cmm/ContFlowOpt.hs
@@ -1,7 +1,7 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE BangPatterns #-}
{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}
-module CmmContFlowOpt
+module GHC.Cmm.ContFlowOpt
( cmmCfgOpts
, cmmCfgOptsProc
, removeUnreachableBlocksProc
@@ -11,14 +11,14 @@ where
import GhcPrelude hiding (succ, unzip, zip)
-import Hoopl.Block
-import Hoopl.Collections
-import Hoopl.Graph
-import Hoopl.Label
-import BlockId
-import Cmm
-import CmmUtils
-import CmmSwitch (mapSwitchTargets, switchTargetsToList)
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Dataflow.Graph
+import GHC.Cmm.Dataflow.Label
+import GHC.Cmm.BlockId
+import GHC.Cmm
+import GHC.Cmm.Utils
+import GHC.Cmm.Switch (mapSwitchTargets, switchTargetsToList)
import Maybes
import Panic
import Util
diff --git a/compiler/cmm/Hoopl/Dataflow.hs b/compiler/GHC/Cmm/Dataflow.hs
index 9762a84..fcabb1d 100644
--- a/compiler/cmm/Hoopl/Dataflow.hs
+++ b/compiler/GHC/Cmm/Dataflow.hs
@@ -17,7 +17,7 @@
-- specialised to the UniqSM monad.
--
-module Hoopl.Dataflow
+module GHC.Cmm.Dataflow
( C, O, Block
, lastNode, entryLabel
, foldNodesBwdOO
@@ -36,7 +36,7 @@ where
import GhcPrelude
-import Cmm
+import GHC.Cmm
import UniqSupply
import Data.Array
@@ -44,10 +44,10 @@ import Data.Maybe
import Data.IntSet (IntSet)
import qualified Data.IntSet as IntSet
-import Hoopl.Block
-import Hoopl.Graph
-import Hoopl.Collections
-import Hoopl.Label
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.Dataflow.Graph
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Dataflow.Label
type family Fact (x :: Extensibility) f :: *
type instance Fact C f = FactBase f
diff --git a/compiler/cmm/Hoopl/Block.hs b/compiler/GHC/Cmm/Dataflow/Block.hs
index 07aafe8..d2e52a8 100644
--- a/compiler/cmm/Hoopl/Block.hs
+++ b/compiler/GHC/Cmm/Dataflow/Block.hs
@@ -6,7 +6,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
-module Hoopl.Block
+module GHC.Cmm.Dataflow.Block
( Extensibility (..)
, O
, C
diff --git a/compiler/cmm/Hoopl/Collections.hs b/compiler/GHC/Cmm/Dataflow/Collections.hs
index 4c5516b..f131f17 100644
--- a/compiler/cmm/Hoopl/Collections.hs
+++ b/compiler/GHC/Cmm/Dataflow/Collections.hs
@@ -4,7 +4,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
-module Hoopl.Collections
+module GHC.Cmm.Dataflow.Collections
( IsSet(..)
, setInsertList, setDeleteList, setUnions
, IsMap(..)
diff --git a/compiler/cmm/Hoopl/Graph.hs b/compiler/GHC/Cmm/Dataflow/Graph.hs
index 992becb..3f361de 100644
--- a/compiler/cmm/Hoopl/Graph.hs
+++ b/compiler/GHC/Cmm/Dataflow/Graph.hs
@@ -5,7 +5,7 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
-module Hoopl.Graph
+module GHC.Cmm.Dataflow.Graph
( Body
, Graph
, Graph'(..)
@@ -23,9 +23,9 @@ module Hoopl.Graph
import GhcPrelude
import Util
-import Hoopl.Label
-import Hoopl.Block
-import Hoopl.Collections
+import GHC.Cmm.Dataflow.Label
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.Dataflow.Collections
-- | A (possibly empty) collection of closed/closed blocks
type Body n = LabelMap (Block n C C)
diff --git a/compiler/cmm/Hoopl/Label.hs b/compiler/GHC/Cmm/Dataflow/Label.hs
index 2e75d97..c571ced 100644
--- a/compiler/cmm/Hoopl/Label.hs
+++ b/compiler/GHC/Cmm/Dataflow/Label.hs
@@ -4,7 +4,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
-module Hoopl.Label
+module GHC.Cmm.Dataflow.Label
( Label
, LabelMap
, LabelSet
@@ -18,7 +18,7 @@ import GhcPrelude
import Outputable
-- TODO: This should really just use GHC's Unique and Uniq{Set,FM}
-import Hoopl.Collections
+import GHC.Cmm.Dataflow.Collections
import Unique (Uniquable(..))
import TrieMap
diff --git a/compiler/cmm/Debug.hs b/compiler/GHC/Cmm/DebugBlock.hs
index 712dd4b..70fc08e 100644
--- a/compiler/cmm/Debug.hs
+++ b/compiler/GHC/Cmm/DebugBlock.hs
@@ -10,7 +10,7 @@
--
-----------------------------------------------------------------------------
-module Debug (
+module GHC.Cmm.DebugBlock (
DebugBlock(..),
cmmDebugGen,
@@ -25,22 +25,22 @@ module Debug (
import GhcPrelude
-import BlockId
-import CLabel
-import Cmm
-import CmmUtils
+import GHC.Cmm.BlockId
+import GHC.Cmm.CLabel
+import GHC.Cmm
+import GHC.Cmm.Utils
import CoreSyn
import FastString ( nilFS, mkFastString )
import Module
import Outputable
-import PprCmmExpr ( pprExpr )
+import GHC.Cmm.Ppr.Expr ( pprExpr )
import SrcLoc
import Util ( seqList )
-import Hoopl.Block
-import Hoopl.Collections
-import Hoopl.Graph
-import Hoopl.Label
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Dataflow.Graph
+import GHC.Cmm.Dataflow.Label
import Data.Maybe
import Data.List ( minimumBy, nubBy )
@@ -316,7 +316,7 @@ with a typical C-- procedure as would come from the STG-to-Cmm code generator,
},
Let's consider how this procedure will be decorated with unwind information
-(largely by CmmLayoutStack). Naturally, when we enter the procedure `entry` the
+(largely by GHC.Cmm.LayoutStack). Naturally, when we enter the procedure `entry` the
value of Sp is no different from what it was at its call site. Therefore we will
add an `unwind` statement saying this at the beginning of its unwind-annotated
code,
@@ -369,7 +369,7 @@ The flow of unwinding information through the compiler is a bit convoluted:
haven't actually done any register assignment or stack layout yet, so there
is no need for unwind information.
- * CmmLayoutStack figures out how to layout each procedure's stack, and produces
+ * GHC.Cmm.LayoutStack figures out how to layout each procedure's stack, and produces
appropriate unwinding nodes for each adjustment of the STG Sp register.
* The unwind nodes are carried through the sinking pass. Currently this is
diff --git a/compiler/cmm/CmmExpr.hs b/compiler/GHC/Cmm/Expr.hs
index 860ee1a..3b4f015 100644
--- a/compiler/cmm/CmmExpr.hs
+++ b/compiler/GHC/Cmm/Expr.hs
@@ -4,7 +4,7 @@
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
-module CmmExpr
+module GHC.Cmm.Expr
( CmmExpr(..), cmmExprType, cmmExprWidth, cmmExprAlignment, maybeInvertCmmExpr
, CmmReg(..), cmmRegType, cmmRegWidth
, CmmLit(..), cmmLitType
@@ -25,17 +25,17 @@ module CmmExpr
, regSetToList
, Area(..)
- , module CmmMachOp
- , module CmmType
+ , module GHC.Cmm.MachOp
+ , module GHC.Cmm.Type
)
where
import GhcPrelude
-import BlockId
-import CLabel
-import CmmMachOp
-import CmmType
+import GHC.Cmm.BlockId
+import GHC.Cmm.CLabel
+import GHC.Cmm.MachOp
+import GHC.Cmm.Type
import DynFlags
import Outputable (panic)
import Unique
@@ -83,7 +83,7 @@ data CmmReg
data Area
= Old -- See Note [Old Area]
| Young {-# UNPACK #-} !BlockId -- Invariant: must be a continuation BlockId
- -- See Note [Continuation BlockId] in CmmNode.
+ -- See Note [Continuation BlockId] in GHC.Cmm.Node.
deriving (Eq, Ord)
{- Note [Old Area]
@@ -200,7 +200,7 @@ data CmmLit
| CmmBlock {-# UNPACK #-} !BlockId -- Code label
-- Invariant: must be a continuation BlockId
- -- See Note [Continuation BlockId] in CmmNode.
+ -- See Note [Continuation BlockId] in GHC.Cmm.Node.
| CmmHighStackMark -- A late-bound constant that stands for the max
-- #bytes of stack space used during a procedure.
@@ -408,7 +408,7 @@ There are no specific rules about which registers might overlap with
which other registers, but presumably it's safe to assume that nothing
will overlap with special registers like Sp or BaseReg.
-Use CmmUtils.regsOverlap to determine whether two GlobalRegs overlap
+Use GHC.Cmm.Utils.regsOverlap to determine whether two GlobalRegs overlap
on a particular platform. The instance Eq GlobalReg is syntactic
equality of STG registers and does not take overlap into
account. However it is still used in UserOfRegs/DefinerOfRegs and
diff --git a/compiler/cmm/MkGraph.hs b/compiler/GHC/Cmm/Graph.hs
index c6e6243..8d19e7f 100644
--- a/compiler/cmm/MkGraph.hs
+++ b/compiler/GHC/Cmm/Graph.hs
@@ -1,6 +1,6 @@
{-# LANGUAGE BangPatterns, GADTs #-}
-module MkGraph
+module GHC.Cmm.Graph
( CmmAGraph, CmmAGraphScoped, CgStmt(..)
, (<*>), catAGraphs
, mkLabel, mkMiddle, mkLast, outOfLine
@@ -23,19 +23,19 @@ where
import GhcPrelude hiding ( (<*>) ) -- avoid importing (<*>)
-import BlockId
-import Cmm
-import CmmCallConv
-import CmmSwitch (SwitchTargets)
+import GHC.Cmm.BlockId
+import GHC.Cmm
+import GHC.Cmm.CallConv
+import GHC.Cmm.Switch (SwitchTargets)
-import Hoopl.Block
-import Hoopl.Graph
-import Hoopl.Label
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.Dataflow.Graph
+import GHC.Cmm.Dataflow.Label
import DynFlags
import FastString
import ForeignCall
import OrdList
-import SMRep (ByteOff)
+import GHC.Runtime.Layout (ByteOff)
import UniqSupply
import Util
import Panic
diff --git a/compiler/cmm/CmmInfo.hs b/compiler/GHC/Cmm/Info.hs
index 3ef3d50..a10db2b 100644
--- a/compiler/cmm/CmmInfo.hs
+++ b/compiler/GHC/Cmm/Info.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE CPP #-}
-module CmmInfo (
+module GHC.Cmm.Info (
mkEmptyContInfoTable,
cmmToRawCmm,
mkInfoTable,
@@ -36,14 +36,14 @@ module CmmInfo (
import GhcPrelude
-import Cmm
-import CmmUtils
-import CLabel
-import SMRep
-import Bitmap
+import GHC.Cmm
+import GHC.Cmm.Utils
+import GHC.Cmm.CLabel
+import GHC.Runtime.Layout
+import GHC.Data.Bitmap
import Stream (Stream)
import qualified Stream
-import Hoopl.Collections
+import GHC.Cmm.Dataflow.Collections
import GHC.Platform
import Maybes
@@ -281,7 +281,7 @@ mkSRTLit dflags _ (Just lbl) = ([CmmLabel lbl], CmmInt 1 (halfWordWidth dflags))
-- | Is the SRT offset field inline in the info table on this platform?
--
-- See the section "Referring to an SRT from the info table" in
--- Note [SRTs] in CmmBuildInfoTables.hs
+-- Note [SRTs] in GHC.Cmm.Info.Build
inlineSRT :: DynFlags -> Bool
inlineSRT dflags = platformArch (targetPlatform dflags) == ArchX86_64
&& tablesNextToCode dflags
diff --git a/compiler/cmm/CmmBuildInfoTables.hs b/compiler/GHC/Cmm/Info/Build.hs
index 81c86fd..1ba79be 100644
--- a/compiler/cmm/CmmBuildInfoTables.hs
+++ b/compiler/GHC/Cmm/Info/Build.hs
@@ -1,7 +1,7 @@
{-# LANGUAGE GADTs, BangPatterns, RecordWildCards,
GeneralizedNewtypeDeriving, NondecreasingIndentation, TupleSections #-}
-module CmmBuildInfoTables
+module GHC.Cmm.Info.Build
( CAFSet, CAFEnv, cafAnal
, doSRTs, ModuleSRTInfo, emptySRT
) where
@@ -9,22 +9,22 @@ module CmmBuildInfoTables
import GhcPrelude hiding (succ)
import Id
-import BlockId
-import Hoopl.Block
-import Hoopl.Graph
-import Hoopl.Label
-import Hoopl.Collections
-import Hoopl.Dataflow
+import GHC.Cmm.BlockId
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.Dataflow.Graph
+import GHC.Cmm.Dataflow.Label
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Dataflow
import Module
import GHC.Platform
import Digraph
-import CLabel
-import Cmm
-import CmmUtils
+import GHC.Cmm.CLabel
+import GHC.Cmm
+import GHC.Cmm.Utils
import DynFlags
import Maybes
import Outputable
-import SMRep
+import GHC.Runtime.Layout
import UniqSupply
import CostCentre
import GHC.StgToCmm.Heap
diff --git a/compiler/cmm/CmmLayoutStack.hs b/compiler/GHC/Cmm/LayoutStack.hs
index e26f287..f6dda77 100644
--- a/compiler/cmm/CmmLayoutStack.hs
+++ b/compiler/GHC/Cmm/LayoutStack.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE BangPatterns, RecordWildCards, GADTs #-}
-module CmmLayoutStack (
+module GHC.Cmm.LayoutStack (
cmmLayoutStack, setInfoTableStackMap
) where
@@ -9,21 +9,21 @@ import GHC.StgToCmm.Utils ( callerSaveVolatileRegs, newTemp ) -- XXX layer
import GHC.StgToCmm.Foreign ( saveThreadState, loadThreadState ) -- XXX layering violation
import BasicTypes
-import Cmm
-import CmmInfo
-import BlockId
-import CLabel
-import CmmUtils
-import MkGraph
+import GHC.Cmm
+import GHC.Cmm.Info
+import GHC.Cmm.BlockId
+import GHC.Cmm.CLabel
+import GHC.Cmm.Utils
+import GHC.Cmm.Graph
import ForeignCall
-import CmmLive
-import CmmProcPoint
-import SMRep
-import Hoopl.Block
-import Hoopl.Collections
-import Hoopl.Dataflow
-import Hoopl.Graph
-import Hoopl.Label
+import GHC.Cmm.Liveness
+import GHC.Cmm.ProcPoint
+import GHC.Runtime.Layout
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Dataflow
+import GHC.Cmm.Dataflow.Graph
+import GHC.Cmm.Dataflow.Label
import UniqSupply
import Maybes
import UniqFM
diff --git a/compiler/cmm/CmmLex.x b/compiler/GHC/Cmm/Lexer.x
index 468ea00..d8f15b9 100644
--- a/compiler/cmm/CmmLex.x
+++ b/compiler/GHC/Cmm/Lexer.x
@@ -11,16 +11,16 @@
-----------------------------------------------------------------------------
{
-module CmmLex (
+module GHC.Cmm.Lexer (
CmmToken(..), cmmlex,
) where
import GhcPrelude
-import CmmExpr
+import GHC.Cmm.Expr
import Lexer
-import CmmMonad
+import GHC.Cmm.Monad
import SrcLoc
import UniqFM
import StringBuffer
diff --git a/compiler/cmm/CmmLint.hs b/compiler/GHC/Cmm/Lint.hs
index 3ad65bd..d70fed3 100644
--- a/compiler/cmm/CmmLint.hs
+++ b/compiler/GHC/Cmm/Lint.hs
@@ -7,28 +7,28 @@
-----------------------------------------------------------------------------
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE GADTs #-}
-module CmmLint (
+module GHC.Cmm.Lint (
cmmLint, cmmLintGraph
) where
import GhcPrelude
-import Hoopl.Block
-import Hoopl.Collections
-import Hoopl.Graph
-import Hoopl.Label
-import Cmm
-import CmmUtils
-import CmmLive
-import CmmSwitch (switchTargetsToList)
-import PprCmm () -- For Outputable instances
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Dataflow.Graph
+import GHC.Cmm.Dataflow.Label
+import GHC.Cmm
+import GHC.Cmm.Utils
+import GHC.Cmm.Liveness
+import GHC.Cmm.Switch (switchTargetsToList)
+import GHC.Cmm.Ppr () -- For Outputable instances
import Outputable
import DynFlags
import Control.Monad (ap)
-- Things to check:
--- - invariant on CmmBlock in CmmExpr (see comment there)
+-- - invariant on CmmBlock in GHC.Cmm.Expr (see comment there)
-- - check for branches to blocks that don't exist
-- - check types
diff --git a/compiler/cmm/CmmLive.hs b/compiler/GHC/Cmm/Liveness.hs
index ca474ef..2b598f5 100644
--- a/compiler/cmm/CmmLive.hs
+++ b/compiler/GHC/Cmm/Liveness.hs
@@ -3,7 +3,7 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
-module CmmLive
+module GHC.Cmm.Liveness
( CmmLocalLive
, cmmLocalLiveness
, cmmGlobalLiveness
@@ -15,13 +15,13 @@ where
import GhcPrelude
import DynFlags
-import BlockId
-import Cmm
-import PprCmmExpr () -- For Outputable instances
-import Hoopl.Block
-import Hoopl.Collections
-import Hoopl.Dataflow
-import Hoopl.Label
+import GHC.Cmm.BlockId
+import GHC.Cmm
+import GHC.Cmm.Ppr.Expr () -- For Outputable instances
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Dataflow
+import GHC.Cmm.Dataflow.Label
import Maybes
import Outputable
diff --git a/compiler/cmm/CmmMachOp.hs b/compiler/GHC/Cmm/MachOp.hs
index 418ebec..2340015 100644
--- a/compiler/cmm/CmmMachOp.hs
+++ b/compiler/GHC/Cmm/MachOp.hs
@@ -1,4 +1,4 @@
-module CmmMachOp
+module GHC.Cmm.MachOp
( MachOp(..)
, pprMachOp, isCommutableMachOp, isAssociativeMachOp
, isComparisonMachOp, maybeIntComparison, machOpResultType
@@ -28,7 +28,7 @@ where
import GhcPrelude
-import CmmType
+import GHC.Cmm.Type
import Outputable
import DynFlags
diff --git a/compiler/cmm/CmmMonad.hs b/compiler/GHC/Cmm/Monad.hs
index a04c4ad..6b8d00a 100644
--- a/compiler/cmm/CmmMonad.hs
+++ b/compiler/GHC/Cmm/Monad.hs
@@ -9,7 +9,7 @@
-- The parser for C-- requires access to a lot more of the 'DynFlags',
-- so 'PD' provides access to 'DynFlags' via a 'HasDynFlags' instance.
-----------------------------------------------------------------------------
-module CmmMonad (
+module GHC.Cmm.Monad (
PD(..)
, liftP
) where
diff --git a/compiler/cmm/CmmNode.hs b/compiler/GHC/Cmm/Node.hs
index f9bad96..bb74647 100644
--- a/compiler/cmm/CmmNode.hs
+++ b/compiler/GHC/Cmm/Node.hs
@@ -12,7 +12,7 @@
-- CmmNode type for representation using Hoopl graphs.
-module CmmNode (
+module GHC.Cmm.Node (
CmmNode(..), CmmFormal, CmmActual, CmmTickish,
UpdFrameOffset, Convention(..),
ForeignConvention(..), ForeignTarget(..), foreignTargetHints,
@@ -27,20 +27,20 @@ module CmmNode (
import GhcPrelude hiding (succ)
import GHC.Platform.Regs
-import CmmExpr
-import CmmSwitch
+import GHC.Cmm.Expr
+import GHC.Cmm.Switch
import DynFlags
import FastString
import ForeignCall
import Outputable
-import SMRep
+import GHC.Runtime.Layout
import CoreSyn (Tickish)
import qualified Unique as U
-import Hoopl.Block
-import Hoopl.Graph
-import Hoopl.Collections
-import Hoopl.Label
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.Dataflow.Graph
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Dataflow.Label
import Data.Maybe
import Data.List (tails,sortBy)
import Unique (nonDetCmpUnique)
@@ -190,7 +190,7 @@ after we've saved Sp all the Cmm optimiser's assumptions are broken.
Note that a safe foreign call needs an info table.
So Safe Foreign Calls must remain as last nodes until the stack is
-made manifest in CmmLayoutStack, where they are lowered into the above
+made manifest in GHC.Cmm.LayoutStack, where they are lowered into the above
sequence.
-}
@@ -225,7 +225,7 @@ code generation in callerSaveVolatileRegs in GHC.StgToCmm.Utils. However,
one result of doing this is that the contents of these registers
may mysteriously change if referenced inside the arguments. This
is dangerous, so you'll need to disable inlining much in the same
-way is done in cmm/CmmOpt.hs currently. We should fix this!
+way is done in GHC.Cmm.Opt currently. We should fix this!
-}
---------------------------------------------
@@ -449,7 +449,7 @@ instance DefinerOfRegs GlobalReg (CmmNode e x) where
-- this we need to treat safe foreign call as if was normal call.
-----------------------------------
--- mapping Expr in CmmNode
+-- mapping Expr in GHC.Cmm.Node
mapForeignTarget :: (CmmExpr -> CmmExpr) -> ForeignTarget -> ForeignTarget
mapForeignTarget exp (ForeignTarget e c) = ForeignTarget (exp e) c
@@ -481,7 +481,7 @@ mapExpDeep :: (CmmExpr -> CmmExpr) -> CmmNode e x -> CmmNode e x
mapExpDeep f = mapExp $ wrapRecExp f
------------------------------------------------------------------------
--- mapping Expr in CmmNode, but not performing allocation if no changes
+-- mapping Expr in GHC.Cmm.Node, but not performing allocation if no changes
mapForeignTargetM :: (CmmExpr -> Maybe CmmExpr) -> ForeignTarget -> Maybe ForeignTarget
mapForeignTargetM f (ForeignTarget e c) = (\x -> ForeignTarget x c) `fmap` f e
@@ -533,7 +533,7 @@ mapExpDeepM :: (CmmExpr -> Maybe CmmExpr) -> CmmNode e x -> Maybe (CmmNode e x)
mapExpDeepM f = mapExpM $ wrapRecExpM f
-----------------------------------
--- folding Expr in CmmNode
+-- folding Expr in GHC.Cmm.Node
foldExpForeignTarget :: (CmmExpr -> z -> z) -> ForeignTarget -> z -> z
foldExpForeignTarget exp (ForeignTarget e _) z = exp e z
diff --git a/compiler/cmm/CmmOpt.hs b/compiler/GHC/Cmm/Opt.hs
index 5b542a3..1db37ae 100644
--- a/compiler/cmm/CmmOpt.hs
+++ b/compiler/GHC/Cmm/Opt.hs
@@ -6,7 +6,7 @@
--
-----------------------------------------------------------------------------
-module CmmOpt (
+module GHC.Cmm.Opt (
constantFoldNode,
constantFoldExpr,
cmmMachOpFold,
@@ -15,8 +15,8 @@ module CmmOpt (
import GhcPrelude
-import CmmUtils
-import Cmm
+import GHC.Cmm.Utils
+import GHC.Cmm
import DynFlags
import Util
diff --git a/compiler/cmm/CmmParse.y b/compiler/GHC/Cmm/Parser.y
index e568378..d7235d0 100644
--- a/compiler/cmm/CmmParse.y
+++ b/compiler/GHC/Cmm/Parser.y
@@ -200,12 +200,12 @@ necessary to the stack to accommodate it (e.g. 2).
{
{-# LANGUAGE TupleSections #-}
-module CmmParse ( parseCmmFile ) where
+module GHC.Cmm.Parser ( parseCmmFile ) where
import GhcPrelude
import GHC.StgToCmm.ExtCode
-import CmmCallConv
+import GHC.Cmm.CallConv
import GHC.StgToCmm.Prof
import GHC.StgToCmm.Heap
import GHC.StgToCmm.Monad hiding ( getCode, getCodeR, getCodeScoped, emitLabel, emit
@@ -219,20 +219,20 @@ import GHC.StgToCmm.Closure
import GHC.StgToCmm.Layout hiding (ArgRep(..))
import GHC.StgToCmm.Ticky
import GHC.StgToCmm.Bind ( emitBlackHoleCode, emitUpdateFrame )
-import CoreSyn ( Tickish(SourceNote) )
-
-import CmmOpt
-import MkGraph
-import Cmm
-import CmmUtils
-import CmmSwitch ( mkSwitchTargets )
-import CmmInfo
-import BlockId
-import CmmLex
-import CLabel
-import SMRep
+import CoreSyn ( Tickish(SourceNote) )
+
+import GHC.Cmm.Opt
+import GHC.Cmm.Graph
+import GHC.Cmm
+import GHC.Cmm.Utils
+import GHC.Cmm.Switch ( mkSwitchTargets )
+import GHC.Cmm.Info
+import GHC.Cmm.BlockId
+import GHC.Cmm.Lexer
+import GHC.Cmm.CLabel
+import GHC.Cmm.Monad
+import GHC.Runtime.Layout
import Lexer
-import CmmMonad
import CostCentre
import ForeignCall
diff --git a/compiler/cmm/CmmPipeline.hs b/compiler/GHC/Cmm/Pipeline.hs
index e7689a6..6db9e23 100644
--- a/compiler/cmm/CmmPipeline.hs
+++ b/compiler/GHC/Cmm/Pipeline.hs
@@ -1,6 +1,6 @@
{-# LANGUAGE BangPatterns #-}
-module CmmPipeline (
+module GHC.Cmm.Pipeline (
-- | Converts C-- with an implicit stack and native C-- calls into
-- optimized, CPS converted and native-call-less C--. The latter
-- C-- can be used to generate assembly.
@@ -9,16 +9,16 @@ module CmmPipeline (
import GhcPrelude
-import Cmm
-import CmmLint
-import CmmBuildInfoTables
-import CmmCommonBlockElim
-import CmmImplementSwitchPlans
-import CmmProcPoint
-import CmmContFlowOpt
-import CmmLayoutStack
-import CmmSink
-import Hoopl.Collections
+import GHC.Cmm
+import GHC.Cmm.Lint
+import GHC.Cmm.Info.Build
+import GHC.Cmm.CommonBlockElim
+import GHC.Cmm.Switch.Implement
+import GHC.Cmm.ProcPoint
+import GHC.Cmm.ContFlowOpt
+import GHC.Cmm.LayoutStack
+import GHC.Cmm.Sink
+import GHC.Cmm.Dataflow.Collections
import UniqSupply
import DynFlags
diff --git a/compiler/cmm/PprCmm.hs b/compiler/GHC/Cmm/Ppr.hs
index 397a666..891cbd9 100644
--- a/compiler/cmm/PprCmm.hs
+++ b/compiler/GHC/Cmm/Ppr.hs
@@ -33,28 +33,28 @@
--
-- A useful example pass over Cmm is in nativeGen/MachCodeGen.hs
-module PprCmm
- ( module PprCmmDecl
- , module PprCmmExpr
+module GHC.Cmm.Ppr
+ ( module GHC.Cmm.Ppr.Decl
+ , module GHC.Cmm.Ppr.Expr
)
where
import GhcPrelude hiding (succ)
-import CLabel
-import Cmm
-import CmmUtils
-import CmmSwitch
+import GHC.Cmm.CLabel
+import GHC.Cmm
+import GHC.Cmm.Utils
+import GHC.Cmm.Switch
import DynFlags
import FastString
import Outputable
-import PprCmmDecl
-import PprCmmExpr
+import GHC.Cmm.Ppr.Decl
+import GHC.Cmm.Ppr.Expr
import Util
import BasicTypes
-import Hoopl.Block
-import Hoopl.Graph
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.Dataflow.Graph
-------------------------------------------------
-- Outputable instances
diff --git a/compiler/cmm/PprCmmDecl.hs b/compiler/GHC/Cmm/Ppr/Decl.hs
index e54abdc..2544e6a 100644
--- a/compiler/cmm/PprCmmDecl.hs
+++ b/compiler/GHC/Cmm/Ppr/Decl.hs
@@ -33,15 +33,15 @@
--
{-# OPTIONS_GHC -fno-warn-orphans #-}
-module PprCmmDecl
+module GHC.Cmm.Ppr.Decl
( writeCmms, pprCmms, pprCmmGroup, pprSection, pprStatic
)
where
import GhcPrelude
-import PprCmmExpr
-import Cmm
+import GHC.Cmm.Ppr.Expr
+import GHC.Cmm
import DynFlags
import Outputable
diff --git a/compiler/cmm/PprCmmExpr.hs b/compiler/GHC/Cmm/Ppr/Expr.hs
index 7bf73f1..53a335e 100644
--- a/compiler/cmm/PprCmmExpr.hs
+++ b/compiler/GHC/Cmm/Ppr/Expr.hs
@@ -33,14 +33,14 @@
--
{-# OPTIONS_GHC -fno-warn-orphans #-}
-module PprCmmExpr
+module GHC.Cmm.Ppr.Expr
( pprExpr, pprLit
)
where
import GhcPrelude
-import CmmExpr
+import GHC.Cmm.Expr
import Outputable
import DynFlags
@@ -83,7 +83,7 @@ pprExpr e
CmmLit lit -> pprLit lit
_other -> pprExpr1 e
--- Here's the precedence table from CmmParse.y:
+-- Here's the precedence table from GHC.Cmm.Parser:
-- %nonassoc '>=' '>' '<=' '<' '!=' '=='
-- %left '|'
-- %left '^'
@@ -154,7 +154,7 @@ genMachOp mop args
-- unary
[x] -> doc <> pprExpr9 x
- _ -> pprTrace "PprCmm.genMachOp: machop with strange number of args"
+ _ -> pprTrace "GHC.Cmm.Ppr.Expr.genMachOp: machop with strange number of args"
(pprMachOp mop <+>
parens (hcat $ punctuate comma (map pprExpr args)))
empty
diff --git a/compiler/cmm/CmmProcPoint.hs b/compiler/GHC/Cmm/ProcPoint.hs
index 746a175..00a7a73 100644
--- a/compiler/cmm/CmmProcPoint.hs
+++ b/compiler/GHC/Cmm/ProcPoint.hs
@@ -1,6 +1,6 @@
{-# LANGUAGE GADTs, DisambiguateRecordFields, BangPatterns #-}
-module CmmProcPoint
+module GHC.Cmm.ProcPoint
( ProcPointSet, Status(..)
, callProcPoints, minimalProcPointSet
, splitAtProcPoints, procPointAnalysis
@@ -11,25 +11,25 @@ where
import GhcPrelude hiding (last, unzip, succ, zip)
import DynFlags
-import BlockId
-import CLabel
-import Cmm
-import PprCmm () -- For Outputable instances
-import CmmUtils
-import CmmInfo
-import CmmLive
-import CmmSwitch
+import GHC.Cmm.BlockId
+import GHC.Cmm.CLabel
+import GHC.Cmm
+import GHC.Cmm.Ppr () -- For Outputable instances
+import GHC.Cmm.Utils
+import GHC.Cmm.Info
+import GHC.Cmm.Liveness
+import GHC.Cmm.Switch
import Data.List (sortBy)
import Maybes
import Control.Monad
import Outputable
import GHC.Platform
import UniqSupply
-import Hoopl.Block
-import Hoopl.Collections
-import Hoopl.Dataflow
-import Hoopl.Graph
-import Hoopl.Label
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Dataflow
+import GHC.Cmm.Dataflow.Graph
+import GHC.Cmm.Dataflow.Label
-- Compute a minimal set of proc points for a control-flow graph.
@@ -386,7 +386,7 @@ splitAtProcPoints dflags entry_label callPPs procPoints procMap
procs
splitAtProcPoints _ _ _ _ _ t@(CmmData _ _) = return [t]
--- Only called from CmmProcPoint.splitAtProcPoints. NB. does a
+-- Only called from GHC.Cmm.ProcPoint.splitAtProcPoints. NB. does a
-- recursive lookup, see comment below.
replaceBranches :: LabelMap BlockId -> CmmGraph -> CmmGraph
replaceBranches env cmmg
diff --git a/compiler/cmm/CmmSink.hs b/compiler/GHC/Cmm/Sink.hs
index 7d945b0..8e231df 100644
--- a/compiler/cmm/CmmSink.hs
+++ b/compiler/GHC/Cmm/Sink.hs
@@ -1,18 +1,18 @@
{-# LANGUAGE GADTs #-}
-module CmmSink (
+module GHC.Cmm.Sink (
cmmSink
) where
import GhcPrelude
-import Cmm
-import CmmOpt
-import CmmLive
-import CmmUtils
-import Hoopl.Block
-import Hoopl.Label
-import Hoopl.Collections
-import Hoopl.Graph
+import GHC.Cmm
+import GHC.Cmm.Opt
+import GHC.Cmm.Liveness
+import GHC.Cmm.Utils
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.Dataflow.Label
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Dataflow.Graph
import GHC.Platform.Regs
import GHC.Platform (isARM, platformArch)
@@ -490,7 +490,7 @@ and apply above transformation to eliminate the comparison against 1.
It's tempting to just turn every != into == and then let cmmMachOpFold
do its thing, but that risks changing a nice fall-through conditional
into one that requires two jumps. (see swapcond_last in
-CmmContFlowOpt), so instead we carefully look for just the cases where
+GHC.Cmm.ContFlowOpt), so instead we carefully look for just the cases where
we can eliminate a comparison.
-}
improveConditional :: CmmNode O x -> CmmNode O x
diff --git a/compiler/cmm/CmmSwitch.hs b/compiler/GHC/Cmm/Switch.hs
index 26bf5c4..e89fadf 100644
--- a/compiler/cmm/CmmSwitch.hs
+++ b/compiler/GHC/Cmm/Switch.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE GADTs #-}
-module CmmSwitch (
+module GHC.Cmm.Switch (
SwitchTargets,
mkSwitchTargets,
switchTargetsCases, switchTargetsDefault, switchTargetsRange, switchTargetsSigned,
@@ -15,7 +15,7 @@ import GhcPrelude
import Outputable
import DynFlags
-import Hoopl.Label (Label)
+import GHC.Cmm.Dataflow.Label (Label)
import Data.Maybe
import Data.List (groupBy)
@@ -32,9 +32,9 @@ import qualified Data.Map as M
--
-- The overall plan is:
-- * The Stg → Cmm transformation creates a single `SwitchTargets` in
--- emitSwitch and emitCmmLitSwitch in GHC.StgToCmm/Utils.hs.
+-- emitSwitch and emitCmmLitSwitch in GHC.StgToCmm.Utils.
-- At this stage, they are unsuitable for code generation.
--- * A dedicated Cmm transformation (CmmImplementSwitchPlans) replaces these
+-- * A dedicated Cmm transformation (GHC.Cmm.Switch.Implement) replaces these
-- switch statements with code that is suitable for code generation, i.e.
-- a nice balanced tree of decisions with dense jump tables in the leafs.
-- The actual planning of this tree is performed in pure code in createSwitchPlan
@@ -42,15 +42,16 @@ import qualified Data.Map as M
-- * The actual code generation will not do any further processing and
-- implement each CmmSwitch with a jump tables.
--
--- When compiling to LLVM or C, CmmImplementSwitchPlans leaves the switch
+-- When compiling to LLVM or C, GHC.Cmm.Switch.Implement leaves the switch
-- statements alone, as we can turn a SwitchTargets value into a nice
-- switch-statement in LLVM resp. C, and leave the rest to the compiler.
--
--- See Note [CmmSwitch vs. CmmImplementSwitchPlans] why the two module are
+-- See Note [GHC.Cmm.Switch vs. GHC.Cmm.Switch.Implement] why the two module are
-- separated.
-----------------------------------------------------------------------------
--- Note [Magic Constants in CmmSwitch]
+-- Note [Magic Constants in GHC.Cmm.Switch]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
--
-- There are a lot of heuristics here that depend on magic values where it is
-- hard to determine the "best" value (for whatever that means). These are the
@@ -78,8 +79,8 @@ minJumpTableOffset = 2
-----------------------------------------------------------------------------
-- Switch Targets
--- Note [SwitchTargets]:
--- ~~~~~~~~~~~~~~~~~~~~~
+-- Note [SwitchTargets]
+-- ~~~~~~~~~~~~~~~~~~~~
--
-- The branches of a switch are stored in a SwitchTargets, which consists of an
-- (optional) default jump target, and a map from values to jump targets.
@@ -209,7 +210,7 @@ switchTargetsFallThrough (SwitchTargets _ _ mbdef branches) = (groups, mbdef)
groupBy ((==) `on` snd) $
M.toList branches
--- | Custom equality helper, needed for "CmmCommonBlockElim"
+-- | Custom equality helper, needed for "GHC.Cmm.CommonBlockElim"
eqSwitchTargetWith :: (Label -> Label -> Bool) -> SwitchTargets -> SwitchTargets -> Bool
eqSwitchTargetWith eq (SwitchTargets signed1 range1 mbdef1 ids1) (SwitchTargets signed2 range2 mbdef2 ids2) =
signed1 == signed2 && range1 == range2 && goMB mbdef1 mbdef2 && goList (M.toList ids1) (M.toList ids2)
@@ -242,7 +243,7 @@ data SwitchPlan
--
-- createSwitchPlan creates such a switch plan, in these steps:
-- 1. It splits the switch statement at segments of non-default values that
--- are too large. See splitAtHoles and Note [Magic Constants in CmmSwitch]
+-- are too large. See splitAtHoles and Note [Magic Constants in GHC.Cmm.Switch]
-- 2. Too small jump tables should be avoided, so we break up smaller pieces
-- in breakTooSmall.
-- 3. We fill in the segments between those pieces with a jump to the default
@@ -478,23 +479,24 @@ reassocTuples initial [] last
reassocTuples initial ((a,b):tuples) last
= (initial,a) : reassocTuples b tuples last
--- Note [CmmSwitch vs. CmmImplementSwitchPlans]
--- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+-- Note [GHC.Cmm.Switch vs. GHC.Cmm.Switch.Implement]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-- I (Joachim) separated the two somewhat closely related modules
--
--- - CmmSwitch, which provides the CmmSwitchTargets type and contains the strategy
+-- - GHC.Cmm.Switch, which provides the CmmSwitchTargets type and contains the strategy
-- for implementing a Cmm switch (createSwitchPlan), and
--- - CmmImplementSwitchPlans, which contains the actual Cmm graph modification,
+-- - GHC.Cmm.Switch.Implement, which contains the actual Cmm graph modification,
--
-- for these reasons:
--
--- * CmmSwitch is very low in the dependency tree, i.e. does not depend on any
--- GHC specific modules at all (with the exception of Output and Hoople
--- (Literal)). CmmImplementSwitchPlans is the Cmm transformation and hence very
--- high in the dependency tree.
--- * CmmSwitch provides the CmmSwitchTargets data type, which is abstract, but
--- used in CmmNodes.
--- * Because CmmSwitch is low in the dependency tree, the separation allows
+-- * GHC.Cmm.Switch is very low in the dependency tree, i.e. does not depend on any
+-- GHC specific modules at all (with the exception of Output and
+-- GHC.Cmm.Dataflow (Literal)).
+-- * GHC.Cmm.Switch.Implement is the Cmm transformation and hence very high in
+-- the dependency tree.
+-- * GHC.Cmm.Switch provides the CmmSwitchTargets data type, which is abstract, but
+-- used in GHC.Cmm.Node.
+-- * Because GHC.Cmm.Switch is low in the dependency tree, the separation allows
-- for more parallelism when building GHC.
-- * The interaction between the modules is very explicit and easy to
-- understand, due to the small and simple interface.
diff --git a/compiler/cmm/CmmImplementSwitchPlans.hs b/compiler/GHC/Cmm/Switch/Implement.hs
index 83c29cf..dfac116 100644
--- a/compiler/cmm/CmmImplementSwitchPlans.hs
+++ b/compiler/GHC/Cmm/Switch/Implement.hs
@@ -1,16 +1,16 @@
{-# LANGUAGE GADTs #-}
-module CmmImplementSwitchPlans
+module GHC.Cmm.Switch.Implement
( cmmImplementSwitchPlans
)
where
import GhcPrelude
-import Hoopl.Block
-import BlockId
-import Cmm
-import CmmUtils
-import CmmSwitch
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.BlockId
+import GHC.Cmm
+import GHC.Cmm.Utils
+import GHC.Cmm.Switch
import UniqSupply
import DynFlags
@@ -20,12 +20,12 @@ import DynFlags
-- assembly code, by proper constructs (if-then-else trees, dense jump tables).
--
-- The actual, abstract strategy is determined by createSwitchPlan in
--- CmmSwitch and returned as a SwitchPlan; here is just the implementation in
--- terms of Cmm code. See Note [Cmm Switches, the general plan] in CmmSwitch.
+-- GHC.Cmm.Switch and returned as a SwitchPlan; here is just the implementation in
+-- terms of Cmm code. See Note [Cmm Switches, the general plan] in GHC.Cmm.Switch.
--
-- This division into different modules is both to clearly separate concerns,
-- but also because createSwitchPlan needs access to the constructors of
--- SwitchTargets, a data type exported abstractly by CmmSwitch.
+-- SwitchTargets, a data type exported abstractly by GHC.Cmm.Switch.
--
-- | Traverses the 'CmmGraph', making sure that 'CmmSwitch' are suitable for
diff --git a/compiler/cmm/CmmType.hs b/compiler/GHC/Cmm/Type.hs
index f8ac71a..867a260 100644
--- a/compiler/cmm/CmmType.hs
+++ b/compiler/GHC/Cmm/Type.hs
@@ -1,4 +1,4 @@
-module CmmType
+module GHC.Cmm.Type
( CmmType -- Abstract
, b8, b16, b32, b64, b128, b256, b512, f32, f64, bWord, bHalfWord, gcWord
, cInt
diff --git a/compiler/cmm/CmmUtils.hs b/compiler/GHC/Cmm/Utils.hs
index 8920d2d..d879c7b 100644
--- a/compiler/cmm/CmmUtils.hs
+++ b/compiler/GHC/Cmm/Utils.hs
@@ -9,7 +9,7 @@
--
-----------------------------------------------------------------------------
-module CmmUtils(
+module GHC.Cmm.Utils(
-- CmmType
primRepCmmType, slotCmmType, slotForeignHint,
typeCmmType, typeForeignHint, primRepForeignHint,
@@ -73,10 +73,10 @@ import GhcPrelude
import TyCon ( PrimRep(..), PrimElemRep(..) )
import GHC.Types.RepType ( UnaryType, SlotTy (..), typePrimRep1 )
-import SMRep
-import Cmm
-import BlockId
-import CLabel
+import GHC.Runtime.Layout
+import GHC.Cmm
+import GHC.Cmm.BlockId
+import GHC.Cmm.CLabel
import Outputable
import DynFlags
import Unique
@@ -85,10 +85,10 @@ import GHC.Platform.Regs
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import Data.Bits
-import Hoopl.Graph
-import Hoopl.Label
-import Hoopl.Block
-import Hoopl.Collections
+import GHC.Cmm.Dataflow.Graph
+import GHC.Cmm.Dataflow.Label
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.Dataflow.Collections
---------------------------------------------------
--
diff --git a/compiler/cmm/cmm-notes b/compiler/GHC/Cmm/cmm-notes
index 699f218..d664a19 100644
--- a/compiler/cmm/cmm-notes
+++ b/compiler/GHC/Cmm/cmm-notes
@@ -19,7 +19,7 @@ Things we did
More notes (June 11)
~~~~~~~~~~~~~~~~~~~~
-* In CmmContFlowOpts.branchChainElim, can a single block be the
+* In CmmContFlowOpt.branchChainElim, can a single block be the
successor of two calls?
* Check in ClosureInfo:
@@ -123,7 +123,7 @@ of calls don't need an info table.
Figuring out proc-points
~~~~~~~~~~~~~~~~~~~~~~~~
Proc-points are identified by
-CmmProcPoint.minimalProcPointSet/extendPPSet Although there isn't
+GHC.Cmm.ProcPoint.minimalProcPointSet/extendPPSet Although there isn't
that much code, JD thinks that it could be done much more nicely using
a dominator analysis, using the Dataflow Engine.
diff --git a/compiler/cmm/PprC.hs b/compiler/GHC/CmmToC.hs
index d94bc01..a413820 100644
--- a/compiler/cmm/PprC.hs
+++ b/compiler/GHC/CmmToC.hs
@@ -18,7 +18,7 @@
--
-----------------------------------------------------------------------------
-module PprC (
+module GHC.CmmToC (
writeC
) where
@@ -27,16 +27,16 @@ module PprC (
-- Cmm stuff
import GhcPrelude
-import BlockId
-import CLabel
+import GHC.Cmm.BlockId
+import GHC.Cmm.CLabel
import ForeignCall
-import Cmm hiding (pprBBlock)
-import PprCmm () -- For Outputable instances
-import Hoopl.Block
-import Hoopl.Collections
-import Hoopl.Graph
-import CmmUtils
-import CmmSwitch
+import GHC.Cmm hiding (pprBBlock)
+import GHC.Cmm.Ppr () -- For Outputable instances
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Dataflow.Graph
+import GHC.Cmm.Utils
+import GHC.Cmm.Switch
-- Utils
import CPrim
diff --git a/compiler/cmm/Bitmap.hs b/compiler/GHC/Data/Bitmap.hs
index 42acc5f..a8eba5e 100644
--- a/compiler/cmm/Bitmap.hs
+++ b/compiler/GHC/Data/Bitmap.hs
@@ -8,7 +8,7 @@
-- places in generated code (stack frame liveness masks, function
-- argument liveness masks, SRT bitmaps).
-module Bitmap (
+module GHC.Data.Bitmap (
Bitmap, mkBitmap,
intsToBitmap, intsToReverseBitmap,
mAX_SMALL_BITMAP_SIZE,
@@ -17,7 +17,7 @@ module Bitmap (
import GhcPrelude
-import SMRep
+import GHC.Runtime.Layout
import DynFlags
import Util
@@ -104,7 +104,7 @@ Note [Strictness when building Bitmaps]
========================================
One of the places where @Bitmap@ is used is in in building Static Reference
-Tables (SRTs) (in @CmmBuildInfoTables.procpointSRT@). In #7450 it was noticed
+Tables (SRTs) (in @GHC.Cmm.Info.Build.procpointSRT@). In #7450 it was noticed
that some test cases (particularly those whose C-- have large numbers of CAFs)
produced large quantities of allocations from this function.
diff --git a/compiler/GHC/Platform/Regs.hs b/compiler/GHC/Platform/Regs.hs
index c304d4f..51f7658 100644
--- a/compiler/GHC/Platform/Regs.hs
+++ b/compiler/GHC/Platform/Regs.hs
@@ -5,7 +5,7 @@ module GHC.Platform.Regs
import GhcPrelude
-import CmmExpr
+import GHC.Cmm.Expr
import GHC.Platform
import Reg
diff --git a/compiler/cmm/SMRep.hs b/compiler/GHC/Runtime/Layout.hs
index fe4ed58..8f24547 100644
--- a/compiler/cmm/SMRep.hs
+++ b/compiler/GHC/Runtime/Layout.hs
@@ -5,7 +5,7 @@
{-# LANGUAGE CPP,GeneralizedNewtypeDeriving #-}
-module SMRep (
+module GHC.Runtime.Layout (
-- * Words and bytes
WordOff, ByteOff,
wordsToBytes, bytesToWordsRoundUp,
diff --git a/compiler/GHC/Stg/Lift/Analysis.hs b/compiler/GHC/Stg/Lift/Analysis.hs
index 02d439c..ccbad37 100644
--- a/compiler/GHC/Stg/Lift/Analysis.hs
+++ b/compiler/GHC/Stg/Lift/Analysis.hs
@@ -26,7 +26,7 @@ import BasicTypes
import Demand
import DynFlags
import Id
-import SMRep ( WordOff )
+import GHC.Runtime.Layout ( WordOff )
import GHC.Stg.Syntax
import qualified GHC.StgToCmm.ArgRep as StgToCmm.ArgRep
import qualified GHC.StgToCmm.Closure as StgToCmm.Closure
diff --git a/compiler/GHC/StgToCmm.hs b/compiler/GHC/StgToCmm.hs
index 10a9dc2..f489ce6 100644
--- a/compiler/GHC/StgToCmm.hs
+++ b/compiler/GHC/StgToCmm.hs
@@ -26,9 +26,9 @@ import GHC.StgToCmm.Closure
import GHC.StgToCmm.Hpc
import GHC.StgToCmm.Ticky
-import Cmm
-import CmmUtils
-import CLabel
+import GHC.Cmm
+import GHC.Cmm.Utils
+import GHC.Cmm.CLabel
import GHC.Stg.Syntax
import DynFlags
@@ -48,7 +48,7 @@ import BasicTypes
import VarSet ( isEmptyDVarSet )
import OrdList
-import MkGraph
+import GHC.Cmm.Graph
import Data.IORef
import Control.Monad (when,void)
diff --git a/compiler/GHC/StgToCmm/ArgRep.hs b/compiler/GHC/StgToCmm/ArgRep.hs
index cc2fe83..347d908 100644
--- a/compiler/GHC/StgToCmm/ArgRep.hs
+++ b/compiler/GHC/StgToCmm/ArgRep.hs
@@ -19,7 +19,7 @@ import GhcPrelude
import GHC.StgToCmm.Closure ( idPrimRep )
-import SMRep ( WordOff )
+import GHC.Runtime.Layout ( WordOff )
import Id ( Id )
import TyCon ( PrimRep(..), primElemRepSizeB )
import BasicTypes ( RepArity )
diff --git a/compiler/GHC/StgToCmm/Bind.hs b/compiler/GHC/StgToCmm/Bind.hs
index b1cb34a..a78ab5c 100644
--- a/compiler/GHC/StgToCmm/Bind.hs
+++ b/compiler/GHC/StgToCmm/Bind.hs
@@ -28,14 +28,14 @@ import GHC.StgToCmm.Utils
import GHC.StgToCmm.Closure
import GHC.StgToCmm.Foreign (emitPrimCall)
-import MkGraph
+import GHC.Cmm.Graph
import CoreSyn ( AltCon(..), tickishIsCode )
-import BlockId
-import SMRep
-import Cmm
-import CmmInfo
-import CmmUtils
-import CLabel
+import GHC.Cmm.BlockId
+import GHC.Runtime.Layout
+import GHC.Cmm
+import GHC.Cmm.Info
+import GHC.Cmm.Utils
+import GHC.Cmm.CLabel
import GHC.Stg.Syntax
import CostCentre
import Id
@@ -105,7 +105,7 @@ cgTopRhsClosure dflags rec id ccs upd_flag args body =
-- We don't generate the static closure here, because we might
-- want to add references to static closures to it later. The
- -- static closure is generated by CmmBuildInfoTables.updInfoSRTs,
+ -- static closure is generated by GHC.Cmm.Info.Build.updInfoSRTs,
-- See Note [SRTs], specifically the [FUN] optimisation.
; let fv_details :: [(NonVoid Id, ByteOff)]
@@ -622,7 +622,7 @@ emitBlackHoleCode node = do
-- unconditionally disabled. -- krc 1/2007
-- Note the eager-blackholing check is here rather than in blackHoleOnEntry,
- -- because emitBlackHoleCode is called from CmmParse.
+ -- because emitBlackHoleCode is called from GHC.Cmm.Parser.
let eager_blackholing = not (gopt Opt_SccProfilingOn dflags)
&& gopt Opt_EagerBlackHoling dflags
diff --git a/compiler/GHC/StgToCmm/CgUtils.hs b/compiler/GHC/StgToCmm/CgUtils.hs
index f3dccd9..58c46f8 100644
--- a/compiler/GHC/StgToCmm/CgUtils.hs
+++ b/compiler/GHC/StgToCmm/CgUtils.hs
@@ -19,11 +19,11 @@ module GHC.StgToCmm.CgUtils (
import GhcPrelude
import GHC.Platform.Regs
-import Cmm
-import Hoopl.Block
-import Hoopl.Graph
-import CmmUtils
-import CLabel
+import GHC.Cmm
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.Dataflow.Graph
+import GHC.Cmm.Utils
+import GHC.Cmm.CLabel
import DynFlags
import Outputable
diff --git a/compiler/GHC/StgToCmm/Closure.hs b/compiler/GHC/StgToCmm/Closure.hs
index df8cb04..724ca60 100644
--- a/compiler/GHC/StgToCmm/Closure.hs
+++ b/compiler/GHC/StgToCmm/Closure.hs
@@ -67,13 +67,13 @@ module GHC.StgToCmm.Closure (
import GhcPrelude
import GHC.Stg.Syntax
-import SMRep
-import Cmm
-import PprCmmExpr() -- For Outputable instances
+import GHC.Runtime.Layout
+import GHC.Cmm
+import GHC.Cmm.Ppr.Expr() -- For Outputable instances
import CostCentre
-import BlockId
-import CLabel
+import GHC.Cmm.BlockId
+import GHC.Cmm.CLabel
import Id
import IdInfo
import DataCon
diff --git a/compiler/GHC/StgToCmm/DataCon.hs b/compiler/GHC/StgToCmm/DataCon.hs
index 1e92966..2bbeaba 100644
--- a/compiler/GHC/StgToCmm/DataCon.hs
+++ b/compiler/GHC/StgToCmm/DataCon.hs
@@ -29,11 +29,11 @@ import GHC.StgToCmm.Layout
import GHC.StgToCmm.Utils
import GHC.StgToCmm.Closure
-import CmmExpr
-import CmmUtils
-import CLabel
-import MkGraph
-import SMRep
+import GHC.Cmm.Expr
+import GHC.Cmm.Utils
+import GHC.Cmm.CLabel
+import GHC.Cmm.Graph
+import GHC.Runtime.Layout
import CostCentre
import Module
import DataCon
diff --git a/compiler/GHC/StgToCmm/Env.hs b/compiler/GHC/StgToCmm/Env.hs
index 45b09a3..b2c1371 100644
--- a/compiler/GHC/StgToCmm/Env.hs
+++ b/compiler/GHC/StgToCmm/Env.hs
@@ -31,14 +31,14 @@ import GHC.StgToCmm.Monad
import GHC.StgToCmm.Utils
import GHC.StgToCmm.Closure
-import CLabel
+import GHC.Cmm.CLabel
-import BlockId
-import CmmExpr
-import CmmUtils
+import GHC.Cmm.BlockId
+import GHC.Cmm.Expr
+import GHC.Cmm.Utils
import DynFlags
import Id
-import MkGraph
+import GHC.Cmm.Graph
import Name
import Outputable
import GHC.Stg.Syntax
diff --git a/compiler/GHC/StgToCmm/Expr.hs b/compiler/GHC/StgToCmm/Expr.hs
index 3836aa3..0c2d9b8 100644
--- a/compiler/GHC/StgToCmm/Expr.hs
+++ b/compiler/GHC/StgToCmm/Expr.hs
@@ -30,10 +30,10 @@ import GHC.StgToCmm.Closure
import GHC.Stg.Syntax
-import MkGraph
-import BlockId
-import Cmm hiding ( succ )
-import CmmInfo
+import GHC.Cmm.Graph
+import GHC.Cmm.BlockId
+import GHC.Cmm hiding ( succ )
+import GHC.Cmm.Info
import CoreSyn
import DataCon
import DynFlags ( mAX_PTR_TAG )
diff --git a/compiler/GHC/StgToCmm/ExtCode.hs b/compiler/GHC/StgToCmm/ExtCode.hs
index 4a5225e..2679ce4 100644
--- a/compiler/GHC/StgToCmm/ExtCode.hs
+++ b/compiler/GHC/StgToCmm/ExtCode.hs
@@ -42,11 +42,11 @@ import GhcPrelude
import qualified GHC.StgToCmm.Monad as F
import GHC.StgToCmm.Monad (FCode, newUnique)
-import Cmm
-import CLabel
-import MkGraph
+import GHC.Cmm
+import GHC.Cmm.CLabel
+import GHC.Cmm.Graph
-import BlockId
+import GHC.Cmm.BlockId
import DynFlags
import FastString
import Module
diff --git a/compiler/GHC/StgToCmm/Foreign.hs b/compiler/GHC/StgToCmm/Foreign.hs
index 3ef0872..62a948d 100644
--- a/compiler/GHC/StgToCmm/Foreign.hs
+++ b/compiler/GHC/StgToCmm/Foreign.hs
@@ -9,7 +9,7 @@
module GHC.StgToCmm.Foreign (
cgForeignCall,
emitPrimCall, emitCCall,
- emitForeignCall, -- For CmmParse
+ emitForeignCall,
emitSaveThreadState,
saveThreadState,
emitLoadThreadState,
@@ -28,14 +28,14 @@ import GHC.StgToCmm.Utils
import GHC.StgToCmm.Closure
import GHC.StgToCmm.Layout
-import BlockId (newBlockId)
-import Cmm
-import CmmUtils
-import MkGraph
+import GHC.Cmm.BlockId (newBlockId)
+import GHC.Cmm
+import GHC.Cmm.Utils
+import GHC.Cmm.Graph
import Type
import GHC.Types.RepType
-import CLabel
-import SMRep
+import GHC.Cmm.CLabel
+import GHC.Runtime.Layout
import ForeignCall
import DynFlags
import Maybes
@@ -202,7 +202,7 @@ emitPrimCall :: [CmmFormal] -> CallishMachOp -> [CmmActual] -> FCode ()
emitPrimCall res op args
= void $ emitForeignCall PlayRisky res (PrimTarget op) args
--- alternative entry point, used by CmmParse
+-- alternative entry point, used by GHC.Cmm.Parser
emitForeignCall
:: Safety
-> [CmmFormal] -- where to put the results
@@ -257,9 +257,9 @@ load_target_into_temp other_target@(PrimTarget _) =
-- Note [Register Parameter Passing]).
--
-- However, we can't pattern-match on the expression here, because
--- this is used in a loop by CmmParse, and testing the expression
+-- this is used in a loop by GHC.Cmm.Parser, and testing the expression
-- results in a black hole. So we always create a temporary, and rely
--- on CmmSink to clean it up later. (Yuck, ToDo). The generated code
+-- on GHC.Cmm.Sink to clean it up later. (Yuck, ToDo). The generated code
-- ends up being the same, at least for the RTS .cmm code.
--
maybe_assign_temp :: CmmExpr -> FCode CmmExpr
diff --git a/compiler/GHC/StgToCmm/Heap.hs b/compiler/GHC/StgToCmm/Heap.hs
index d36cad5..492a446 100644
--- a/compiler/GHC/StgToCmm/Heap.hs
+++ b/compiler/GHC/StgToCmm/Heap.hs
@@ -23,7 +23,7 @@ module GHC.StgToCmm.Heap (
import GhcPrelude hiding ((<*>))
import GHC.Stg.Syntax
-import CLabel
+import GHC.Cmm.CLabel
import GHC.StgToCmm.Layout
import GHC.StgToCmm.Utils
import GHC.StgToCmm.Monad
@@ -32,13 +32,13 @@ import GHC.StgToCmm.Ticky
import GHC.StgToCmm.Closure
import GHC.StgToCmm.Env
-import MkGraph
+import GHC.Cmm.Graph
-import Hoopl.Label
-import SMRep
-import BlockId
-import Cmm
-import CmmUtils
+import GHC.Cmm.Dataflow.Label
+import GHC.Runtime.Layout
+import GHC.Cmm.BlockId
+import GHC.Cmm
+import GHC.Cmm.Utils
import CostCentre
import IdInfo( CafInfo(..), mayHaveCafRefs )
import Id ( Id )
@@ -337,7 +337,7 @@ entryHeapCheck cl_info nodeSet arity args code
Just (_, ArgGen _) -> False
_otherwise -> True
--- | lower-level version for CmmParse
+-- | lower-level version for GHC.Cmm.Parser
entryHeapCheck' :: Bool -- is a known function pattern
-> CmmExpr -- expression for the closure pointer
-> Int -- Arity -- not same as len args b/c of voids
diff --git a/compiler/GHC/StgToCmm/Hpc.hs b/compiler/GHC/StgToCmm/Hpc.hs
index e33d392..a3f4112 100644
--- a/compiler/GHC/StgToCmm/Hpc.hs
+++ b/compiler/GHC/StgToCmm/Hpc.hs
@@ -12,11 +12,11 @@ import GhcPrelude
import GHC.StgToCmm.Monad
-import MkGraph
-import CmmExpr
-import CLabel
+import GHC.Cmm.Graph
+import GHC.Cmm.Expr
+import GHC.Cmm.CLabel
import Module
-import CmmUtils
+import GHC.Cmm.Utils
import GHC.StgToCmm.Utils
import HscTypes
import DynFlags
diff --git a/compiler/GHC/StgToCmm/Layout.hs b/compiler/GHC/StgToCmm/Layout.hs
index 6d7825e..e78221d 100644
--- a/compiler/GHC/StgToCmm/Layout.hs
+++ b/compiler/GHC/StgToCmm/Layout.hs
@@ -41,13 +41,13 @@ import GHC.StgToCmm.Ticky
import GHC.StgToCmm.Monad
import GHC.StgToCmm.Utils
-import MkGraph
-import SMRep
-import BlockId
-import Cmm
-import CmmUtils
-import CmmInfo
-import CLabel
+import GHC.Cmm.Graph
+import GHC.Runtime.Layout
+import GHC.Cmm.BlockId
+import GHC.Cmm
+import GHC.Cmm.Utils
+import GHC.Cmm.Info
+import GHC.Cmm.CLabel
import GHC.Stg.Syntax
import Id
import TyCon ( PrimRep(..), primRepSizeB )
diff --git a/compiler/GHC/StgToCmm/Monad.hs b/compiler/GHC/StgToCmm/Monad.hs
index 716cbda..4f7d2e1 100644
--- a/compiler/GHC/StgToCmm/Monad.hs
+++ b/compiler/GHC/StgToCmm/Monad.hs
@@ -61,14 +61,14 @@ module GHC.StgToCmm.Monad (
import GhcPrelude hiding( sequence, succ )
-import Cmm
+import GHC.Cmm
import GHC.StgToCmm.Closure
import DynFlags
-import Hoopl.Collections
-import MkGraph
-import BlockId
-import CLabel
-import SMRep
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Graph as CmmGraph
+import GHC.Cmm.BlockId
+import GHC.Cmm.CLabel
+import GHC.Runtime.Layout
import Module
import Id
import VarEnv
@@ -369,7 +369,7 @@ addCodeBlocksFrom :: CgState -> CgState -> CgState
-- Add code blocks from the latter to the former
-- (The cgs_stmts will often be empty, but not always; see codeOnly)
s1 `addCodeBlocksFrom` s2
- = s1 { cgs_stmts = cgs_stmts s1 MkGraph.<*> cgs_stmts s2,
+ = s1 { cgs_stmts = cgs_stmts s1 CmmGraph.<*> cgs_stmts s2,
cgs_tops = cgs_tops s1 `appOL` cgs_tops s2 }
@@ -715,7 +715,7 @@ emitStore l r = emitCgStmt (CgStmt (CmmStore l r))
emit :: CmmAGraph -> FCode ()
emit ag
= do { state <- getState
- ; setState $ state { cgs_stmts = cgs_stmts state MkGraph.<*> ag } }
+ ; setState $ state { cgs_stmts = cgs_stmts state CmmGraph.<*> ag } }
emitDecl :: CmmDecl -> FCode ()
emitDecl decl
@@ -743,7 +743,7 @@ emitProcWithStackFrame conv mb_info lbl stk_args args (graph, tscope) True
-- do layout
= do { dflags <- getDynFlags
; let (offset, live, entry) = mkCallEntry dflags conv args stk_args
- graph' = entry MkGraph.<*> graph
+ graph' = entry CmmGraph.<*> graph
; emitProc mb_info lbl live (graph', tscope) offset True
}
emitProcWithStackFrame _ _ _ _ _ _ _ = panic "emitProcWithStackFrame"
diff --git a/compiler/GHC/StgToCmm/Prim.hs b/compiler/GHC/StgToCmm/Prim.hs
index e469e15..0626409 100644
--- a/compiler/GHC/StgToCmm/Prim.hs
+++ b/compiler/GHC/StgToCmm/Prim.hs
@@ -36,17 +36,17 @@ import GHC.StgToCmm.Prof ( costCentreFrom )
import DynFlags
import GHC.Platform
import BasicTypes
-import BlockId
-import MkGraph
+import GHC.Cmm.BlockId
+import GHC.Cmm.Graph
import GHC.Stg.Syntax
-import Cmm
+import GHC.Cmm
import Module ( rtsUnitId )
import Type ( Type, tyConAppTyCon )
import TyCon
-import CLabel
-import CmmUtils
+import GHC.Cmm.CLabel
+import GHC.Cmm.Utils
import PrimOp
-import SMRep
+import GHC.Runtime.Layout
import FastString
import Outputable
import Util
@@ -1525,7 +1525,7 @@ emitPrimOp dflags = \case
-- `quot` and `rem` with constant divisor can be implemented with fast bit-ops
-- (shift, .&.).
--
- -- Currently we only support optimization (performed in CmmOpt) when the
+ -- Currently we only support optimization (performed in GHC.Cmm.Opt) when the
-- constant is a power of 2. #9041 tracks the implementation of the general
-- optimization.
--
diff --git a/compiler/GHC/StgToCmm/Prof.hs b/compiler/GHC/StgToCmm/Prof.hs
index 4743b79..cf5ce5a 100644
--- a/compiler/GHC/StgToCmm/Prof.hs
+++ b/compiler/GHC/StgToCmm/Prof.hs
@@ -28,12 +28,12 @@ import GhcPrelude
import GHC.StgToCmm.Closure
import GHC.StgToCmm.Utils
import GHC.StgToCmm.Monad
-import SMRep
+import GHC.Runtime.Layout
-import MkGraph
-import Cmm
-import CmmUtils
-import CLabel
+import GHC.Cmm.Graph
+import GHC.Cmm
+import GHC.Cmm.Utils
+import GHC.Cmm.CLabel
import CostCentre
import DynFlags
diff --git a/compiler/GHC/StgToCmm/Ticky.hs b/compiler/GHC/StgToCmm/Ticky.hs
index 9eeb134..6e2e2d3 100644
--- a/compiler/GHC/StgToCmm/Ticky.hs
+++ b/compiler/GHC/StgToCmm/Ticky.hs
@@ -23,9 +23,9 @@ Some of the relevant source files:
* some codeGen/ modules import this one
- * this module imports cmm/CLabel.hs to manage labels
+ * this module imports GHC.Cmm.CLabel to manage labels
- * cmm/CmmParse.y expands some macros using generators defined in
+ * GHC.Cmm.Parser expands some macros using generators defined in
this module
* includes/stg/Ticky.h declares all of the global counters
@@ -112,11 +112,11 @@ import GHC.StgToCmm.Utils
import GHC.StgToCmm.Monad
import GHC.Stg.Syntax
-import CmmExpr
-import MkGraph
-import CmmUtils
-import CLabel
-import SMRep
+import GHC.Cmm.Expr
+import GHC.Cmm.Graph
+import GHC.Cmm.Utils
+import GHC.Cmm.CLabel
+import GHC.Runtime.Layout
import Module
import Name
@@ -517,7 +517,7 @@ tickyAllocHeap genuine hp
--------------------------------------------------------------------------------
--- these three are only called from CmmParse.y (ie ultimately from the RTS)
+-- these three are only called from GHC.Cmm.Parser (ie ultimately from the RTS)
-- the units are bytes
diff --git a/compiler/GHC/StgToCmm/Utils.hs b/compiler/GHC/StgToCmm/Utils.hs
index 34fb934..7a784ea 100644
--- a/compiler/GHC/StgToCmm/Utils.hs
+++ b/compiler/GHC/StgToCmm/Utils.hs
@@ -52,20 +52,20 @@ import GhcPrelude
import GHC.StgToCmm.Monad
import GHC.StgToCmm.Closure
-import Cmm
-import BlockId
-import MkGraph
+import GHC.Cmm
+import GHC.Cmm.BlockId
+import GHC.Cmm.Graph as CmmGraph
import GHC.Platform.Regs
-import CLabel
-import CmmUtils
-import CmmSwitch
+import GHC.Cmm.CLabel
+import GHC.Cmm.Utils
+import GHC.Cmm.Switch
import GHC.StgToCmm.CgUtils
import ForeignCall
import IdInfo
import Type
import TyCon
-import SMRep
+import GHC.Runtime.Layout
import Module
import Literal
import Digraph
@@ -458,8 +458,8 @@ mk_discrete_switch _ _tag_expr [(_tag,lbl)] Nothing _
-- In that situation we can be sure the (:) case
-- can't happen, so no need to test
--- SOMETHING MORE COMPLICATED: defer to CmmImplementSwitchPlans
--- See Note [Cmm Switches, the general plan] in CmmSwitch
+-- SOMETHING MORE COMPLICATED: defer to GHC.Cmm.Switch.Implement
+-- See Note [Cmm Switches, the general plan] in GHC.Cmm.Switch
mk_discrete_switch signed tag_expr branches mb_deflt range
= mkSwitch tag_expr $ mkSwitchTargets signed range mb_deflt (M.fromList branches)
@@ -568,7 +568,7 @@ label_code :: BlockId -> CmmAGraphScoped -> FCode BlockId
-- and returns L
label_code join_lbl (code,tsc) = do
lbl <- newBlockId
- emitOutOfLine lbl (code MkGraph.<*> mkBranch join_lbl, tsc)
+ emitOutOfLine lbl (code CmmGraph.<*> mkBranch join_lbl, tsc)
return lbl
--------------
diff --git a/compiler/basicTypes/Unique.hs b/compiler/basicTypes/Unique.hs
index 4a646aa..f14f22d 100644
--- a/compiler/basicTypes/Unique.hs
+++ b/compiler/basicTypes/Unique.hs
@@ -276,7 +276,7 @@ The alternatives are:
is controlled. See Module.ModuleEnv
3) Change the algorithm to use nonDetCmpUnique and document why it's still
deterministic
- 4) Use TrieMap as done in CmmCommonBlockElim.groupByLabel
+ 4) Use TrieMap as done in GHC.Cmm.CommonBlockElim.groupByLabel
-}
instance Eq Unique where
diff --git a/compiler/cmm/BlockId.hs-boot b/compiler/cmm/BlockId.hs-boot
deleted file mode 100644
index 3ad4141..0000000
--- a/compiler/cmm/BlockId.hs-boot
+++ /dev/null
@@ -1,8 +0,0 @@
-module BlockId (BlockId, mkBlockId) where
-
-import Hoopl.Label (Label)
-import Unique (Unique)
-
-type BlockId = Label
-
-mkBlockId :: Unique -> BlockId
diff --git a/compiler/deSugar/Coverage.hs b/compiler/deSugar/Coverage.hs
index 75eeb07..d94f640 100644
--- a/compiler/deSugar/Coverage.hs
+++ b/compiler/deSugar/Coverage.hs
@@ -41,7 +41,7 @@ import TyCon
import BasicTypes
import MonadUtils
import Maybes
-import CLabel
+import GHC.Cmm.CLabel
import Util
import Data.Time
diff --git a/compiler/deSugar/DsForeign.hs b/compiler/deSugar/DsForeign.hs
index 0a3755e..cdf58e7 100644
--- a/compiler/deSugar/DsForeign.hs
+++ b/compiler/deSugar/DsForeign.hs
@@ -37,8 +37,8 @@ import Coercion
import TcEnv
import TcType
-import CmmExpr
-import CmmUtils
+import GHC.Cmm.Expr
+import GHC.Cmm.Utils
import HscTypes
import ForeignCall
import TysWiredIn
diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in
index 640f325..ddcf2ae 100644
--- a/compiler/ghc.cabal.in
+++ b/compiler/ghc.cabal.in
@@ -203,7 +203,7 @@ Library
DataCon
PatSyn
Demand
- Debug
+ GHC.Cmm.DebugBlock
Exception
FieldLabel
GhcMonad
@@ -240,42 +240,42 @@ Library
VarEnv
VarSet
UnVarGraph
- BlockId
- CLabel
- Cmm
- CmmBuildInfoTables
- CmmPipeline
- CmmCallConv
- CmmCommonBlockElim
- CmmImplementSwitchPlans
- CmmContFlowOpt
- CmmExpr
- CmmInfo
- CmmLex
- CmmLint
- CmmLive
- CmmMachOp
- CmmMonad
- CmmSwitch
- CmmNode
- CmmOpt
- CmmParse
- CmmProcPoint
- CmmSink
- CmmType
- CmmUtils
- CmmLayoutStack
+ GHC.Cmm.BlockId
+ GHC.Cmm.CLabel
+ GHC.Cmm
+ GHC.Cmm.Info.Build
+ GHC.Cmm.Pipeline
+ GHC.Cmm.CallConv
+ GHC.Cmm.CommonBlockElim
+ GHC.Cmm.Switch.Implement
+ GHC.Cmm.ContFlowOpt
+ GHC.Cmm.Expr
+ GHC.Cmm.Info
+ GHC.Cmm.Lexer
+ GHC.Cmm.Lint
+ GHC.Cmm.Liveness
+ GHC.Cmm.MachOp
+ GHC.Cmm.Monad
+ GHC.Cmm.Switch
+ GHC.Cmm.Node
+ GHC.Cmm.Opt
+ GHC.Cmm.Parser
+ GHC.Cmm.ProcPoint
+ GHC.Cmm.Sink
+ GHC.Cmm.Type
+ GHC.Cmm.Utils
+ GHC.Cmm.LayoutStack
CliOption
EnumSet
GhcNameVersion
FileSettings
- MkGraph
+ GHC.Cmm.Graph
PprBase
- PprC
- PprCmm
- PprCmmDecl
- PprCmmExpr
- Bitmap
+ GHC.CmmToC
+ GHC.Cmm.Ppr
+ GHC.Cmm.Ppr.Decl
+ GHC.Cmm.Ppr.Expr
+ GHC.Data.Bitmap
GHC.Platform.Regs
GHC.Platform.ARM
GHC.Platform.ARM64
@@ -303,7 +303,7 @@ Library
GHC.StgToCmm.Ticky
GHC.StgToCmm.Utils
GHC.StgToCmm.ExtCode
- SMRep
+ GHC.Runtime.Layout
CoreArity
CoreFVs
CoreLint
@@ -576,11 +576,11 @@ Library
UniqMap
UniqSet
Util
- Hoopl.Block
- Hoopl.Collections
- Hoopl.Dataflow
- Hoopl.Graph
- Hoopl.Label
+ GHC.Cmm.Dataflow
+ GHC.Cmm.Dataflow.Block
+ GHC.Cmm.Dataflow.Collections
+ GHC.Cmm.Dataflow.Graph
+ GHC.Cmm.Dataflow.Label
Exposed-Modules:
AsmCodeGen
diff --git a/compiler/ghci/ByteCodeAsm.hs b/compiler/ghci/ByteCodeAsm.hs
index 82de143..801cdc7 100644
--- a/compiler/ghci/ByteCodeAsm.hs
+++ b/compiler/ghci/ByteCodeAsm.hs
@@ -30,7 +30,7 @@ import Literal
import TyCon
import FastString
import GHC.StgToCmm.Layout ( ArgRep(..) )
-import SMRep
+import GHC.Runtime.Layout
import DynFlags
import Outputable
import GHC.Platform
diff --git a/compiler/ghci/ByteCodeGen.hs b/compiler/ghci/ByteCodeGen.hs
index 2e24bf5..186d094 100644
--- a/compiler/ghci/ByteCodeGen.hs
+++ b/compiler/ghci/ByteCodeGen.hs
@@ -50,8 +50,8 @@ import FastString
import Panic
import GHC.StgToCmm.Closure ( NonVoid(..), fromNonVoid, nonVoidIds )
import GHC.StgToCmm.Layout
-import SMRep hiding (WordOff, ByteOff, wordsToBytes)
-import Bitmap
+import GHC.Runtime.Layout hiding (WordOff, ByteOff, wordsToBytes)
+import GHC.Data.Bitmap
import OrdList
import Maybes
import VarEnv
diff --git a/compiler/ghci/ByteCodeInstr.hs b/compiler/ghci/ByteCodeInstr.hs
index b0db198..9cdd297 100644
--- a/compiler/ghci/ByteCodeInstr.hs
+++ b/compiler/ghci/ByteCodeInstr.hs
@@ -28,7 +28,7 @@ import Literal
import DataCon
import VarSet
import PrimOp
-import SMRep
+import GHC.Runtime.Layout
import Data.Word
import GHC.Stack.CCS (CostCentre)
diff --git a/compiler/ghci/RtClosureInspect.hs b/compiler/ghci/RtClosureInspect.hs
index 96df8b5..a523ae0 100644
--- a/compiler/ghci/RtClosureInspect.hs
+++ b/compiler/ghci/RtClosureInspect.hs
@@ -58,7 +58,7 @@ import DynFlags
import Outputable as Ppr
import GHC.Char
import GHC.Exts.Heap
-import SMRep ( roundUpTo )
+import GHC.Runtime.Layout ( roundUpTo )
import Control.Monad
import Data.Maybe
diff --git a/compiler/llvmGen/LlvmCodeGen.hs b/compiler/llvmGen/LlvmCodeGen.hs
index 0fc7e76..8bff8fd 100644
--- a/compiler/llvmGen/LlvmCodeGen.hs
+++ b/compiler/llvmGen/LlvmCodeGen.hs
@@ -18,9 +18,9 @@ import LlvmCodeGen.Regs
import LlvmMangler
import GHC.StgToCmm.CgUtils ( fixStgRegisters )
-import Cmm
-import Hoopl.Collections
-import PprCmm
+import GHC.Cmm
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Ppr
import BufWrite
import DynFlags
diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs
index ce9f220..165f733 100644
--- a/compiler/llvmGen/LlvmCodeGen/Base.hs
+++ b/compiler/llvmGen/LlvmCodeGen/Base.hs
@@ -44,12 +44,12 @@ import GhcPrelude
import Llvm
import LlvmCodeGen.Regs
-import CLabel
+import GHC.Cmm.CLabel
import GHC.Platform.Regs ( activeStgRegs )
import DynFlags
import FastString
-import Cmm hiding ( succ )
-import CmmUtils ( regsOverlap )
+import GHC.Cmm hiding ( succ )
+import GHC.Cmm.Utils (regsOverlap)
import Outputable as Outp
import GHC.Platform
import UniqFM
diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
index bfaf770..f9b1067 100644
--- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
+++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
@@ -13,16 +13,16 @@ import Llvm
import LlvmCodeGen.Base
import LlvmCodeGen.Regs
-import BlockId
+import GHC.Cmm.BlockId
import GHC.Platform.Regs ( activeStgRegs )
-import CLabel
-import Cmm
-import PprCmm
-import CmmUtils
-import CmmSwitch
-import Hoopl.Block
-import Hoopl.Graph
-import Hoopl.Collections
+import GHC.Cmm.CLabel
+import GHC.Cmm
+import GHC.Cmm.Ppr as PprCmm
+import GHC.Cmm.Utils
+import GHC.Cmm.Switch
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.Dataflow.Graph
+import GHC.Cmm.Dataflow.Collections
import DynFlags
import FastString
diff --git a/compiler/llvmGen/LlvmCodeGen/Data.hs b/compiler/llvmGen/LlvmCodeGen/Data.hs
index 4c07f8e..46fb1af 100644
--- a/compiler/llvmGen/LlvmCodeGen/Data.hs
+++ b/compiler/llvmGen/LlvmCodeGen/Data.hs
@@ -14,9 +14,9 @@ import GhcPrelude
import Llvm
import LlvmCodeGen.Base
-import BlockId
-import CLabel
-import Cmm
+import GHC.Cmm.BlockId
+import GHC.Cmm.CLabel
+import GHC.Cmm
import DynFlags
import GHC.Platform
diff --git a/compiler/llvmGen/LlvmCodeGen/Ppr.hs b/compiler/llvmGen/LlvmCodeGen/Ppr.hs
index 3f29133..5fcc72f 100644
--- a/compiler/llvmGen/LlvmCodeGen/Ppr.hs
+++ b/compiler/llvmGen/LlvmCodeGen/Ppr.hs
@@ -15,8 +15,8 @@ import Llvm
import LlvmCodeGen.Base
import LlvmCodeGen.Data
-import CLabel
-import Cmm
+import GHC.Cmm.CLabel
+import GHC.Cmm
import FastString
import Outputable
diff --git a/compiler/llvmGen/LlvmCodeGen/Regs.hs b/compiler/llvmGen/LlvmCodeGen/Regs.hs
index 8cdf3c6..4b1a156 100644
--- a/compiler/llvmGen/LlvmCodeGen/Regs.hs
+++ b/compiler/llvmGen/LlvmCodeGen/Regs.hs
@@ -15,7 +15,7 @@ import GhcPrelude
import Llvm
-import CmmExpr
+import GHC.Cmm.Expr
import DynFlags
import FastString
import Outputable ( panic )
diff --git a/compiler/main/CodeOutput.hs b/compiler/main/CodeOutput.hs
index 2b9770c..6656a4f 100644
--- a/compiler/main/CodeOutput.hs
+++ b/compiler/main/CodeOutput.hs
@@ -18,10 +18,10 @@ import LlvmCodeGen ( llvmCodeGen )
import UniqSupply ( mkSplitUniqSupply )
import Finder ( mkStubPaths )
-import PprC ( writeC )
-import CmmLint ( cmmLint )
+import GHC.CmmToC ( writeC )
+import GHC.Cmm.Lint ( cmmLint )
import Packages
-import Cmm ( RawCmmGroup )
+import GHC.Cmm ( RawCmmGroup )
import HscTypes
import DynFlags
import Stream ( Stream )
diff --git a/compiler/main/Hooks.hs b/compiler/main/Hooks.hs
index d5ced7d..8caebfc 100644
--- a/compiler/main/Hooks.hs
+++ b/compiler/main/Hooks.hs
@@ -50,7 +50,7 @@ import TyCon
import CostCentre
import GHC.Stg.Syntax
import Stream
-import Cmm
+import GHC.Cmm
import GHC.Hs.Extension
import Data.Maybe
diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs
index ffb9b3c..1c27542 100644
--- a/compiler/main/HscMain.hs
+++ b/compiler/main/HscMain.hs
@@ -133,11 +133,11 @@ import CostCentre
import ProfInit
import TyCon
import Name
-import Cmm
-import CmmParse ( parseCmmFile )
-import CmmBuildInfoTables
-import CmmPipeline
-import CmmInfo
+import GHC.Cmm
+import GHC.Cmm.Parser ( parseCmmFile )
+import GHC.Cmm.Info.Build
+import GHC.Cmm.Pipeline
+import GHC.Cmm.Info
import CodeOutput
import InstEnv
import FamInstEnv
diff --git a/compiler/main/StaticPtrTable.hs b/compiler/main/StaticPtrTable.hs
index 4f67ba0..dfc5479 100644
--- a/compiler/main/StaticPtrTable.hs
+++ b/compiler/main/StaticPtrTable.hs
@@ -124,7 +124,7 @@ Here is a running example:
import GhcPrelude
-import CLabel
+import GHC.Cmm.CLabel
import CoreSyn
import CoreUtils (collectMakeStaticArgs)
import DataCon
diff --git a/compiler/nativeGen/AsmCodeGen.hs b/compiler/nativeGen/AsmCodeGen.hs
index 556c943..021fbae 100644
--- a/compiler/nativeGen/AsmCodeGen.hs
+++ b/compiler/nativeGen/AsmCodeGen.hs
@@ -67,18 +67,18 @@ import Reg
import NCGMonad
import CFG
import Dwarf
-import Debug
+import GHC.Cmm.DebugBlock
-import BlockId
+import GHC.Cmm.BlockId
import GHC.StgToCmm.CgUtils ( fixStgRegisters )
-import Cmm
-import CmmUtils
-import Hoopl.Collections
-import Hoopl.Label
-import Hoopl.Block
-import CmmOpt ( cmmMachOpFold )
-import PprCmm
-import CLabel
+import GHC.Cmm
+import GHC.Cmm.Utils
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Dataflow.Label
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.Opt ( cmmMachOpFold )
+import GHC.Cmm.Ppr
+import GHC.Cmm.CLabel
import UniqFM
import UniqSupply
@@ -826,7 +826,7 @@ computeUnwinding _ ncgImpl (CmmProc _ _ _ (ListGraph blks)) =
-- relevant register writes within a procedure.
--
-- However, the only unwinding information that we care about in GHC is for
- -- Sp. The fact that CmmLayoutStack already ensures that we have unwind
+ -- Sp. The fact that GHC.Cmm.LayoutStack already ensures that we have unwind
-- information at the beginning of every block means that there is no need
-- to perform this sort of push-down.
mapFromList [ (blk_lbl, extractUnwindPoints ncgImpl instrs)
diff --git a/compiler/nativeGen/BlockLayout.hs b/compiler/nativeGen/BlockLayout.hs
index 5e81316..3f74065 100644
--- a/compiler/nativeGen/BlockLayout.hs
+++ b/compiler/nativeGen/BlockLayout.hs
@@ -20,10 +20,10 @@ import Instruction
import NCGMonad
import CFG
-import BlockId
-import Cmm
-import Hoopl.Collections
-import Hoopl.Label
+import GHC.Cmm.BlockId
+import GHC.Cmm
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Dataflow.Label
import DynFlags (gopt, GeneralFlag(..), DynFlags, backendMaintainsCfg)
import UniqFM
@@ -35,7 +35,7 @@ import Outputable
import Maybes
-- DEBUGGING ONLY
---import Debug
+--import GHC.Cmm.DebugBlock
--import Debug.Trace
import ListSetOps (removeDups)
diff --git a/compiler/nativeGen/CFG.hs b/compiler/nativeGen/CFG.hs
index 4dc5f9c..9057322 100644
--- a/compiler/nativeGen/CFG.hs
+++ b/compiler/nativeGen/CFG.hs
@@ -46,15 +46,15 @@ where
import GhcPrelude
-import BlockId
-import Cmm
+import GHC.Cmm.BlockId
+import GHC.Cmm as Cmm
-import CmmUtils
-import CmmSwitch
-import Hoopl.Collections
-import Hoopl.Label
-import Hoopl.Block
-import qualified Hoopl.Graph as G
+import GHC.Cmm.Utils
+import GHC.Cmm.Switch
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Dataflow.Label
+import GHC.Cmm.Dataflow.Block
+import qualified GHC.Cmm.Dataflow.Graph as G
import Util
import Digraph
@@ -74,11 +74,10 @@ import Data.Bifunctor
import Outputable
-- DEBUGGING ONLY
---import Debug
--- import Debug.Trace
+--import GHC.Cmm.DebugBlock
--import OrdList
---import Debug.Trace
-import PprCmm () -- For Outputable instances
+--import GHC.Cmm.DebugBlock.Trace
+import GHC.Cmm.Ppr () -- For Outputable instances
import qualified DynFlags as D
import Data.List
@@ -250,7 +249,7 @@ filterEdges f cfg =
{- Note [Updating the CFG during shortcutting]
See Note [What is shortcutting] in the control flow optimization
-code (CmmContFlowOpt.hs) for a slightly more in depth explanation on shortcutting.
+code (GHC.Cmm.ContFlowOpt) for a slightly more in depth explanation on shortcutting.
In the native backend we shortcut jumps at the assembly level. (AsmCodeGen.hs)
This means we remove blocks containing only one jump from the code
diff --git a/compiler/nativeGen/CPrim.hs b/compiler/nativeGen/CPrim.hs
index 17e5cda..344e62d 100644
--- a/compiler/nativeGen/CPrim.hs
+++ b/compiler/nativeGen/CPrim.hs
@@ -16,8 +16,8 @@ module CPrim
import GhcPrelude
-import CmmType
-import CmmMachOp
+import GHC.Cmm.Type
+import GHC.Cmm.MachOp
import Outputable
popCntLabel :: Width -> String
diff --git a/compiler/nativeGen/Dwarf.hs b/compiler/nativeGen/Dwarf.hs
index 33f1c5b..a64df28 100644
--- a/compiler/nativeGen/Dwarf.hs
+++ b/compiler/nativeGen/Dwarf.hs
@@ -4,11 +4,11 @@ module Dwarf (
import GhcPrelude
-import CLabel
-import CmmExpr ( GlobalReg(..) )
+import GHC.Cmm.CLabel
+import GHC.Cmm.Expr ( GlobalReg(..) )
import Config ( cProjectName, cProjectVersion )
import CoreSyn ( Tickish(..) )
-import Debug
+import GHC.Cmm.DebugBlock
import DynFlags
import Module
import Outputable
@@ -28,8 +28,8 @@ import qualified Data.Map as Map
import System.FilePath
import System.Directory ( getCurrentDirectory )
-import qualified Hoopl.Label as H
-import qualified Hoopl.Collections as H
+import qualified GHC.Cmm.Dataflow.Label as H
+import qualified GHC.Cmm.Dataflow.Collections as H
-- | Generate DWARF/debug information
dwarfGen :: DynFlags -> ModLocation -> UniqSupply -> [DebugBlock]
diff --git a/compiler/nativeGen/Dwarf/Types.hs b/compiler/nativeGen/Dwarf/Types.hs
index a6ba596..df578e2 100644
--- a/compiler/nativeGen/Dwarf/Types.hs
+++ b/compiler/nativeGen/Dwarf/Types.hs
@@ -24,9 +24,9 @@ module Dwarf.Types
import GhcPrelude
-import Debug
-import CLabel
-import CmmExpr ( GlobalReg(..) )
+import GHC.Cmm.DebugBlock
+import GHC.Cmm.CLabel
+import GHC.Cmm.Expr ( GlobalReg(..) )
import Encoding
import FastString
import Outputable
diff --git a/compiler/nativeGen/Format.hs b/compiler/nativeGen/Format.hs
index 745d1e7..d7b6f6b 100644
--- a/compiler/nativeGen/Format.hs
+++ b/compiler/nativeGen/Format.hs
@@ -22,7 +22,7 @@ where
import GhcPrelude
-import Cmm
+import GHC.Cmm
import Outputable
-- It looks very like the old MachRep, but it's now of purely local
diff --git a/compiler/nativeGen/Instruction.hs b/compiler/nativeGen/Instruction.hs
index 4f18a45..150bd8a 100644
--- a/compiler/nativeGen/Instruction.hs
+++ b/compiler/nativeGen/Instruction.hs
@@ -18,11 +18,11 @@ import GhcPrelude
import Reg
-import BlockId
-import Hoopl.Collections
-import Hoopl.Label
+import GHC.Cmm.BlockId
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Dataflow.Label
import DynFlags
-import Cmm hiding (topInfoTable)
+import GHC.Cmm hiding (topInfoTable)
import GHC.Platform
-- | Holds a list of source and destination registers used by a
diff --git a/compiler/nativeGen/NCGMonad.hs b/compiler/nativeGen/NCGMonad.hs
index e1bb927..b963623 100644
--- a/compiler/nativeGen/NCGMonad.hs
+++ b/compiler/nativeGen/NCGMonad.hs
@@ -49,11 +49,11 @@ import Reg
import Format
import TargetReg
-import BlockId
-import Hoopl.Collections
-import Hoopl.Label
-import CLabel ( CLabel )
-import Debug
+import GHC.Cmm.BlockId
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Dataflow.Label
+import GHC.Cmm.CLabel ( CLabel )
+import GHC.Cmm.DebugBlock
import FastString ( FastString )
import UniqFM
import UniqSupply
@@ -65,7 +65,7 @@ import Control.Monad ( ap )
import Instruction
import Outputable (SDoc, pprPanic, ppr)
-import Cmm (RawCmmDecl, CmmStatics)
+import GHC.Cmm (RawCmmDecl, CmmStatics)
import CFG
data NcgImpl statics instr jumpDest = NcgImpl {
diff --git a/compiler/nativeGen/PIC.hs b/compiler/nativeGen/PIC.hs
index 760ba79..e4aba00 100644
--- a/compiler/nativeGen/PIC.hs
+++ b/compiler/nativeGen/PIC.hs
@@ -60,14 +60,14 @@ import Reg
import NCGMonad
-import Hoopl.Collections
-import Cmm
-import CLabel ( CLabel, ForeignLabelSource(..), pprCLabel,
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm
+import GHC.Cmm.CLabel ( CLabel, ForeignLabelSource(..), pprCLabel,
mkDynamicLinkerLabel, DynamicLinkerLabelInfo(..),
dynamicLinkerLabelInfo, mkPicBaseLabel,
labelDynamic, externallyVisibleCLabel )
-import CLabel ( mkForeignLabel )
+import GHC.Cmm.CLabel ( mkForeignLabel )
import BasicTypes
diff --git a/compiler/nativeGen/PPC/CodeGen.hs b/compiler/nativeGen/PPC/CodeGen.hs
index e669630..4d9a38b 100644
--- a/compiler/nativeGen/PPC/CodeGen.hs
+++ b/compiler/nativeGen/PPC/CodeGen.hs
@@ -42,14 +42,14 @@ import TargetReg
import GHC.Platform
-- Our intermediate code:
-import BlockId
-import PprCmm ( pprExpr )
-import Cmm
-import CmmUtils
-import CmmSwitch
-import CLabel
-import Hoopl.Block
-import Hoopl.Graph
+import GHC.Cmm.BlockId
+import GHC.Cmm.Ppr ( pprExpr )
+import GHC.Cmm
+import GHC.Cmm.Utils
+import GHC.Cmm.Switch
+import GHC.Cmm.CLabel
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.Dataflow.Graph
-- The rest:
import OrdList
diff --git a/compiler/nativeGen/PPC/Instr.hs b/compiler/nativeGen/PPC/Instr.hs
index 69aa954..d19282f 100644
--- a/compiler/nativeGen/PPC/Instr.hs
+++ b/compiler/nativeGen/PPC/Instr.hs
@@ -33,14 +33,14 @@ import RegClass
import Reg
import GHC.Platform.Regs
-import BlockId
-import Hoopl.Collections
-import Hoopl.Label
+import GHC.Cmm.BlockId
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Dataflow.Label
import DynFlags
-import Cmm
-import CmmInfo
+import GHC.Cmm
+import GHC.Cmm.Info
import FastString
-import CLabel
+import GHC.Cmm.CLabel
import Outputable
import GHC.Platform
import UniqFM (listToUFM, lookupUFM)
diff --git a/compiler/nativeGen/PPC/Ppr.hs b/compiler/nativeGen/PPC/Ppr.hs
index ea0b36f..9669076 100644
--- a/compiler/nativeGen/PPC/Ppr.hs
+++ b/compiler/nativeGen/PPC/Ppr.hs
@@ -21,13 +21,13 @@ import Reg
import RegClass
import TargetReg
-import Cmm hiding (topInfoTable)
-import Hoopl.Collections
-import Hoopl.Label
+import GHC.Cmm hiding (topInfoTable)
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Dataflow.Label
-import BlockId
-import CLabel
-import PprCmmExpr () -- For Outputable instances
+import GHC.Cmm.BlockId
+import GHC.Cmm.CLabel
+import GHC.Cmm.Ppr.Expr () -- For Outputable instances
import Unique ( pprUniqueAlways, getUnique )
import GHC.Platform
diff --git a/compiler/nativeGen/PPC/RegInfo.hs b/compiler/nativeGen/PPC/RegInfo.hs
index 5ed0ccd..e99a693 100644
--- a/compiler/nativeGen/PPC/RegInfo.hs
+++ b/compiler/nativeGen/PPC/RegInfo.hs
@@ -23,9 +23,9 @@ import GhcPrelude
import PPC.Instr
-import BlockId
-import Cmm
-import CLabel
+import GHC.Cmm.BlockId
+import GHC.Cmm
+import GHC.Cmm.CLabel
import Unique
import Outputable (ppr, text, Outputable, (<>))
diff --git a/compiler/nativeGen/PPC/Regs.hs b/compiler/nativeGen/PPC/Regs.hs
index b008790..66aa006 100644
--- a/compiler/nativeGen/PPC/Regs.hs
+++ b/compiler/nativeGen/PPC/Regs.hs
@@ -55,8 +55,8 @@ import Reg
import RegClass
import Format
-import Cmm
-import CLabel ( CLabel )
+import GHC.Cmm
+import GHC.Cmm.CLabel ( CLabel )
import Unique
import GHC.Platform.Regs
diff --git a/compiler/nativeGen/PprBase.hs b/compiler/nativeGen/PprBase.hs
index 48e9e26..c5574b3 100644
--- a/compiler/nativeGen/PprBase.hs
+++ b/compiler/nativeGen/PprBase.hs
@@ -23,8 +23,8 @@ where
import GhcPrelude
import AsmUtils
-import CLabel
-import Cmm
+import GHC.Cmm.CLabel
+import GHC.Cmm
import DynFlags
import FastString
import Outputable
diff --git a/compiler/nativeGen/RegAlloc/Graph/Coalesce.hs b/compiler/nativeGen/RegAlloc/Graph/Coalesce.hs
index 5ca2412..f42ff94 100644
--- a/compiler/nativeGen/RegAlloc/Graph/Coalesce.hs
+++ b/compiler/nativeGen/RegAlloc/Graph/Coalesce.hs
@@ -9,7 +9,7 @@ import RegAlloc.Liveness
import Instruction
import Reg
-import Cmm
+import GHC.Cmm
import Bag
import Digraph
import UniqFM
diff --git a/compiler/nativeGen/RegAlloc/Graph/Spill.hs b/compiler/nativeGen/RegAlloc/Graph/Spill.hs
index 22a88c0..9ffb51e 100644
--- a/compiler/nativeGen/RegAlloc/Graph/Spill.hs
+++ b/compiler/nativeGen/RegAlloc/Graph/Spill.hs
@@ -12,9 +12,9 @@ import GhcPrelude
import RegAlloc.Liveness
import Instruction
import Reg
-import Cmm hiding (RegSet)
-import BlockId
-import Hoopl.Collections
+import GHC.Cmm hiding (RegSet)
+import GHC.Cmm.BlockId
+import GHC.Cmm.Dataflow.Collections
import MonadUtils
import State
diff --git a/compiler/nativeGen/RegAlloc/Graph/SpillClean.hs b/compiler/nativeGen/RegAlloc/Graph/SpillClean.hs
index 79dbf63..bd8b449 100644
--- a/compiler/nativeGen/RegAlloc/Graph/SpillClean.hs
+++ b/compiler/nativeGen/RegAlloc/Graph/SpillClean.hs
@@ -35,15 +35,15 @@ import RegAlloc.Liveness
import Instruction
import Reg
-import BlockId
-import Cmm
+import GHC.Cmm.BlockId
+import GHC.Cmm
import UniqSet
import UniqFM
import Unique
import State
import Outputable
import GHC.Platform
-import Hoopl.Collections
+import GHC.Cmm.Dataflow.Collections
import Data.List
import Data.Maybe
diff --git a/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs b/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs
index 42de550..4870bf5 100644
--- a/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs
+++ b/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs
@@ -22,9 +22,9 @@ import Reg
import GraphBase
-import Hoopl.Collections (mapLookup)
-import Hoopl.Label
-import Cmm
+import GHC.Cmm.Dataflow.Collections (mapLookup)
+import GHC.Cmm.Dataflow.Label
+import GHC.Cmm
import UniqFM
import UniqSet
import Digraph (flattenSCCs)
diff --git a/compiler/nativeGen/RegAlloc/Linear/Base.hs b/compiler/nativeGen/RegAlloc/Linear/Base.hs
index ad0fafb..3c6965c 100644
--- a/compiler/nativeGen/RegAlloc/Linear/Base.hs
+++ b/compiler/nativeGen/RegAlloc/Linear/Base.hs
@@ -28,7 +28,7 @@ import Outputable
import Unique
import UniqFM
import UniqSupply
-import BlockId
+import GHC.Cmm.BlockId
-- | Used to store the register assignment on entry to a basic block.
diff --git a/compiler/nativeGen/RegAlloc/Linear/JoinToTargets.hs b/compiler/nativeGen/RegAlloc/Linear/JoinToTargets.hs
index 546d48a..c21ab1b 100644
--- a/compiler/nativeGen/RegAlloc/Linear/JoinToTargets.hs
+++ b/compiler/nativeGen/RegAlloc/Linear/JoinToTargets.hs
@@ -18,8 +18,8 @@ import RegAlloc.Liveness
import Instruction
import Reg
-import BlockId
-import Hoopl.Collections
+import GHC.Cmm.BlockId
+import GHC.Cmm.Dataflow.Collections
import Digraph
import DynFlags
import Outputable
diff --git a/compiler/nativeGen/RegAlloc/Linear/Main.hs b/compiler/nativeGen/RegAlloc/Linear/Main.hs
index eac9194..bccffb2 100644
--- a/compiler/nativeGen/RegAlloc/Linear/Main.hs
+++ b/compiler/nativeGen/RegAlloc/Linear/Main.hs
@@ -119,9 +119,9 @@ import RegAlloc.Liveness
import Instruction
import Reg
-import BlockId
-import Hoopl.Collections
-import Cmm hiding (RegSet)
+import GHC.Cmm.BlockId
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm hiding (RegSet)
import Digraph
import DynFlags
@@ -777,7 +777,7 @@ allocateRegsAndSpill reading keep spills alloc (r:rs)
-- NOTE: if the input to the NCG contains some
-- unreachable blocks with junk code, this panic
-- might be triggered. Make sure you only feed
- -- sensible code into the NCG. In CmmPipeline we
+ -- sensible code into the NCG. In GHC.Cmm.Pipeline we
-- call removeUnreachableBlocks at the end for this
-- reason.
diff --git a/compiler/nativeGen/RegAlloc/Linear/State.hs b/compiler/nativeGen/RegAlloc/Linear/State.hs
index 43b8f6c..d24690f 100644
--- a/compiler/nativeGen/RegAlloc/Linear/State.hs
+++ b/compiler/nativeGen/RegAlloc/Linear/State.hs
@@ -44,7 +44,7 @@ import RegAlloc.Linear.Base
import RegAlloc.Liveness
import Instruction
import Reg
-import BlockId
+import GHC.Cmm.BlockId
import DynFlags
import Unique
diff --git a/compiler/nativeGen/RegAlloc/Liveness.hs b/compiler/nativeGen/RegAlloc/Liveness.hs
index a5a9b50..c39ee48 100644
--- a/compiler/nativeGen/RegAlloc/Liveness.hs
+++ b/compiler/nativeGen/RegAlloc/Liveness.hs
@@ -40,11 +40,11 @@ import GhcPrelude
import Reg
import Instruction
-import BlockId
+import GHC.Cmm.BlockId
import CFG
-import Hoopl.Collections
-import Hoopl.Label
-import Cmm hiding (RegSet, emptyRegSet)
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Dataflow.Label
+import GHC.Cmm hiding (RegSet, emptyRegSet)
import Digraph
import DynFlags
diff --git a/compiler/nativeGen/SPARC/CodeGen.hs b/compiler/nativeGen/SPARC/CodeGen.hs
index 46b29d0..d8cda40 100644
--- a/compiler/nativeGen/SPARC/CodeGen.hs
+++ b/compiler/nativeGen/SPARC/CodeGen.hs
@@ -39,15 +39,15 @@ import Format
import NCGMonad ( NatM, getNewRegNat, getNewLabelNat )
-- Our intermediate code:
-import BlockId
-import Cmm
-import CmmUtils
-import CmmSwitch
-import Hoopl.Block
-import Hoopl.Graph
+import GHC.Cmm.BlockId
+import GHC.Cmm
+import GHC.Cmm.Utils
+import GHC.Cmm.Switch
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.Dataflow.Graph
import PIC
import Reg
-import CLabel
+import GHC.Cmm.CLabel
import CPrim
-- The rest:
diff --git a/compiler/nativeGen/SPARC/CodeGen/Amode.hs b/compiler/nativeGen/SPARC/CodeGen/Amode.hs
index 33e3f53..5351fc0 100644
--- a/compiler/nativeGen/SPARC/CodeGen/Amode.hs
+++ b/compiler/nativeGen/SPARC/CodeGen/Amode.hs
@@ -16,7 +16,7 @@ import SPARC.Base
import NCGMonad
import Format
-import Cmm
+import GHC.Cmm
import OrdList
diff --git a/compiler/nativeGen/SPARC/CodeGen/Base.hs b/compiler/nativeGen/SPARC/CodeGen/Base.hs
index 8a2f2f5..4497e1b 100644
--- a/compiler/nativeGen/SPARC/CodeGen/Base.hs
+++ b/compiler/nativeGen/SPARC/CodeGen/Base.hs
@@ -24,8 +24,8 @@ import Reg
import GHC.Platform.Regs
import DynFlags
-import Cmm
-import PprCmmExpr () -- For Outputable instances
+import GHC.Cmm
+import GHC.Cmm.Ppr.Expr () -- For Outputable instances
import GHC.Platform
import Outputable
diff --git a/compiler/nativeGen/SPARC/CodeGen/CondCode.hs b/compiler/nativeGen/SPARC/CodeGen/CondCode.hs
index e6b2e17..892cbb1 100644
--- a/compiler/nativeGen/SPARC/CodeGen/CondCode.hs
+++ b/compiler/nativeGen/SPARC/CodeGen/CondCode.hs
@@ -18,7 +18,7 @@ import SPARC.Base
import NCGMonad
import Format
-import Cmm
+import GHC.Cmm
import OrdList
import Outputable
diff --git a/compiler/nativeGen/SPARC/CodeGen/Expand.hs b/compiler/nativeGen/SPARC/CodeGen/Expand.hs
index 2373119..ba75776 100644
--- a/compiler/nativeGen/SPARC/CodeGen/Expand.hs
+++ b/compiler/nativeGen/SPARC/CodeGen/Expand.hs
@@ -14,7 +14,7 @@ import SPARC.Regs
import Instruction
import Reg
import Format
-import Cmm
+import GHC.Cmm
import Outputable
diff --git a/compiler/nativeGen/SPARC/CodeGen/Gen32.hs b/compiler/nativeGen/SPARC/CodeGen/Gen32.hs
index a7a1f60..a4f6214 100644
--- a/compiler/nativeGen/SPARC/CodeGen/Gen32.hs
+++ b/compiler/nativeGen/SPARC/CodeGen/Gen32.hs
@@ -23,7 +23,7 @@ import NCGMonad
import Format
import Reg
-import Cmm
+import GHC.Cmm
import Control.Monad (liftM)
import DynFlags
diff --git a/compiler/nativeGen/SPARC/CodeGen/Gen32.hs-boot b/compiler/nativeGen/SPARC/CodeGen/Gen32.hs-boot
index 43632c6..1dbd2d3 100644
--- a/compiler/nativeGen/SPARC/CodeGen/Gen32.hs-boot
+++ b/compiler/nativeGen/SPARC/CodeGen/Gen32.hs-boot
@@ -10,7 +10,7 @@ import SPARC.CodeGen.Base
import NCGMonad
import Reg
-import Cmm
+import GHC.Cmm
getSomeReg :: CmmExpr -> NatM (Reg, InstrBlock)
getRegister :: CmmExpr -> NatM Register
diff --git a/compiler/nativeGen/SPARC/CodeGen/Gen64.hs b/compiler/nativeGen/SPARC/CodeGen/Gen64.hs
index 18df9e1..a267cd2 100644
--- a/compiler/nativeGen/SPARC/CodeGen/Gen64.hs
+++ b/compiler/nativeGen/SPARC/CodeGen/Gen64.hs
@@ -22,7 +22,7 @@ import Instruction
import Format
import Reg
-import Cmm
+import GHC.Cmm
import DynFlags
import OrdList
diff --git a/compiler/nativeGen/SPARC/CodeGen/Sanity.hs b/compiler/nativeGen/SPARC/CodeGen/Sanity.hs
index 7f9bfed..b60c958 100644
--- a/compiler/nativeGen/SPARC/CodeGen/Sanity.hs
+++ b/compiler/nativeGen/SPARC/CodeGen/Sanity.hs
@@ -12,7 +12,7 @@ import SPARC.Instr
import SPARC.Ppr () -- For Outputable instances
import Instruction
-import Cmm
+import GHC.Cmm
import Outputable
diff --git a/compiler/nativeGen/SPARC/Imm.hs b/compiler/nativeGen/SPARC/Imm.hs
index bd2d4ab..78b6612 100644
--- a/compiler/nativeGen/SPARC/Imm.hs
+++ b/compiler/nativeGen/SPARC/Imm.hs
@@ -9,8 +9,8 @@ where
import GhcPrelude
-import Cmm
-import CLabel
+import GHC.Cmm
+import GHC.Cmm.CLabel
import Outputable
diff --git a/compiler/nativeGen/SPARC/Instr.hs b/compiler/nativeGen/SPARC/Instr.hs
index c26cfcc..43edfc6 100644
--- a/compiler/nativeGen/SPARC/Instr.hs
+++ b/compiler/nativeGen/SPARC/Instr.hs
@@ -38,11 +38,11 @@ import RegClass
import Reg
import Format
-import CLabel
+import GHC.Cmm.CLabel
import GHC.Platform.Regs
-import BlockId
+import GHC.Cmm.BlockId
import DynFlags
-import Cmm
+import GHC.Cmm
import FastString
import Outputable
import GHC.Platform
diff --git a/compiler/nativeGen/SPARC/Ppr.hs b/compiler/nativeGen/SPARC/Ppr.hs
index 5c7d9fa..7e40f0d 100644
--- a/compiler/nativeGen/SPARC/Ppr.hs
+++ b/compiler/nativeGen/SPARC/Ppr.hs
@@ -37,12 +37,12 @@ import Reg
import Format
import PprBase
-import Cmm hiding (topInfoTable)
-import PprCmm() -- For Outputable instances
-import BlockId
-import CLabel
-import Hoopl.Label
-import Hoopl.Collections
+import GHC.Cmm hiding (topInfoTable)
+import GHC.Cmm.Ppr() -- For Outputable instances
+import GHC.Cmm.BlockId
+import GHC.Cmm.CLabel
+import GHC.Cmm.Dataflow.Label
+import GHC.Cmm.Dataflow.Collections
import Unique ( pprUniqueAlways )
import Outputable
diff --git a/compiler/nativeGen/SPARC/ShortcutJump.hs b/compiler/nativeGen/SPARC/ShortcutJump.hs
index e2a8a71..02d51de 100644
--- a/compiler/nativeGen/SPARC/ShortcutJump.hs
+++ b/compiler/nativeGen/SPARC/ShortcutJump.hs
@@ -13,9 +13,9 @@ import GhcPrelude
import SPARC.Instr
import SPARC.Imm
-import CLabel
-import BlockId
-import Cmm
+import GHC.Cmm.CLabel
+import GHC.Cmm.BlockId
+import GHC.Cmm
import Panic
import Outputable
diff --git a/compiler/nativeGen/X86/CodeGen.hs b/compiler/nativeGen/X86/CodeGen.hs
index 8cea28d..14e7cb5 100644
--- a/compiler/nativeGen/X86/CodeGen.hs
+++ b/compiler/nativeGen/X86/CodeGen.hs
@@ -44,7 +44,7 @@ import X86.RegInfo
import GHC.Platform.Regs
import CPrim
-import Debug ( DebugBlock(..), UnwindPoint(..), UnwindTable
+import GHC.Cmm.DebugBlock ( DebugBlock(..), UnwindPoint(..), UnwindTable
, UnwindExpr(UwReg), toUnwindExpr )
import Instruction
import PIC
@@ -59,16 +59,16 @@ import GHC.Platform
-- Our intermediate code:
import BasicTypes
-import BlockId
+import GHC.Cmm.BlockId
import Module ( primUnitId )
-import CmmUtils
-import CmmSwitch
-import Cmm
-import Hoopl.Block
-import Hoopl.Collections
-import Hoopl.Graph
-import Hoopl.Label
-import CLabel
+import GHC.Cmm.Utils
+import GHC.Cmm.Switch
+import GHC.Cmm
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Dataflow.Graph
+import GHC.Cmm.Dataflow.Label
+import GHC.Cmm.CLabel
import CoreSyn ( Tickish(..) )
import SrcLoc ( srcSpanFile, srcSpanStartLine, srcSpanStartCol )
@@ -360,7 +360,7 @@ stmtToInstrs bid stmt = do
CmmBranch id -> return $ genBranch id
--We try to arrange blocks such that the likely branch is the fallthrough
- --in CmmContFlowOpt. So we can assume the condition is likely false here.
+ --in GHC.Cmm.ContFlowOpt. So we can assume the condition is likely false here.
CmmCondBranch arg true false _ -> genCondBranch bid true false arg
CmmSwitch arg ids -> do dflags <- getDynFlags
genSwitch dflags arg ids
diff --git a/compiler/nativeGen/X86/Instr.hs b/compiler/nativeGen/X86/Instr.hs
index 80a2c8b..4591464 100644
--- a/compiler/nativeGen/X86/Instr.hs
+++ b/compiler/nativeGen/X86/Instr.hs
@@ -26,22 +26,22 @@ import RegClass
import Reg
import TargetReg
-import BlockId
-import Hoopl.Collections
-import Hoopl.Label
+import GHC.Cmm.BlockId
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Dataflow.Label
import GHC.Platform.Regs
-import Cmm
+import GHC.Cmm
import FastString
import Outputable
import GHC.Platform
import BasicTypes (Alignment)
-import CLabel
+import GHC.Cmm.CLabel
import DynFlags
import UniqSet
import Unique
import UniqSupply
-import Debug (UnwindTable)
+import GHC.Cmm.DebugBlock (UnwindTable)
import Control.Monad
import Data.Maybe (fromMaybe)
diff --git a/compiler/nativeGen/X86/Ppr.hs b/compiler/nativeGen/X86/Ppr.hs
index 76a8069..d857a95 100644
--- a/compiler/nativeGen/X86/Ppr.hs
+++ b/compiler/nativeGen/X86/Ppr.hs
@@ -33,13 +33,13 @@ import Reg
import PprBase
-import Hoopl.Collections
-import Hoopl.Label
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Dataflow.Label
import BasicTypes (Alignment, mkAlignment, alignmentBytes)
import DynFlags
-import Cmm hiding (topInfoTable)
-import BlockId
-import CLabel
+import GHC.Cmm hiding (topInfoTable)
+import GHC.Cmm.BlockId
+import GHC.Cmm.CLabel
import Unique ( pprUniqueAlways )
import GHC.Platform
import FastString
diff --git a/compiler/nativeGen/X86/Regs.hs b/compiler/nativeGen/X86/Regs.hs
index 24cdff8..44f9201 100644
--- a/compiler/nativeGen/X86/Regs.hs
+++ b/compiler/nativeGen/X86/Regs.hs
@@ -55,8 +55,8 @@ import GHC.Platform.Regs
import Reg
import RegClass
-import Cmm
-import CLabel ( CLabel )
+import GHC.Cmm
+import GHC.Cmm.CLabel ( CLabel )
import DynFlags
import Outputable
import GHC.Platform
diff --git a/compiler/prelude/PrimOp.hs b/compiler/prelude/PrimOp.hs
index c51304b..81d643f 100644
--- a/compiler/prelude/PrimOp.hs
+++ b/compiler/prelude/PrimOp.hs
@@ -30,7 +30,7 @@ import GhcPrelude
import TysPrim
import TysWiredIn
-import CmmType
+import GHC.Cmm.Type
import Demand
import Id ( Id, mkVanillaGlobalWithInfo )
import IdInfo ( vanillaIdInfo, setCafInfo, CafInfo(NoCafRefs) )
diff --git a/compiler/profiling/ProfInit.hs b/compiler/profiling/ProfInit.hs
index 931299a..f8dc882 100644
--- a/compiler/profiling/ProfInit.hs
+++ b/compiler/profiling/ProfInit.hs
@@ -10,7 +10,7 @@ module ProfInit (profilingInitCode) where
import GhcPrelude
-import CLabel
+import GHC.Cmm.CLabel
import CostCentre
import DynFlags
import Outputable
diff --git a/ghc.mk b/ghc.mk
index 83a2853..a7ebdfb 100644
--- a/ghc.mk
+++ b/ghc.mk
@@ -1217,8 +1217,8 @@ sdist-ghc-prep-tree :
# Add files generated by alex and happy.
# These rules depend on sdist-ghc-prep-tree.
-$(eval $(call sdist-ghc-file,compiler,stage2,cmm,CmmLex,x))
-$(eval $(call sdist-ghc-file,compiler,stage2,cmm,CmmParse,y))
+$(eval $(call sdist-ghc-file,compiler,stage2,GHC,Cmm,Lexer,x))
+$(eval $(call sdist-ghc-file,compiler,stage2,GHC,Cmm,Parser,y))
$(eval $(call sdist-ghc-file,compiler,stage2,parser,Lexer,x))
$(eval $(call sdist-ghc-file,compiler,stage2,parser,Parser,y))
$(eval $(call sdist-ghc-file,utils/hpc,dist-install,,HpcParser,y))
diff --git a/hadrian/src/Rules.hs b/hadrian/src/Rules.hs
index 3f6397f..08f8b57 100644
--- a/hadrian/src/Rules.hs
+++ b/hadrian/src/Rules.hs
@@ -54,8 +54,8 @@ toolArgsTarget = do
need [ root -/- dir -/- "Config.hs" ]
need [ root -/- dir -/- "Parser.hs" ]
need [ root -/- dir -/- "Lexer.hs" ]
- need [ root -/- dir -/- "CmmParse.hs" ]
- need [ root -/- dir -/- "CmmLex.hs" ]
+ need [ root -/- dir -/- "GHC" -/- "Cmm" -/- "Parser.hs" ]
+ need [ root -/- dir -/- "GHC" -/- "Cmm" -/- "Lexer.hs" ]
-- Find out the arguments that are needed to load a module into the
-- session
diff --git a/hadrian/src/Rules/SourceDist.hs b/hadrian/src/Rules/SourceDist.hs
index 8eb215d..b6b41f1 100644
--- a/hadrian/src/Rules/SourceDist.hs
+++ b/hadrian/src/Rules/SourceDist.hs
@@ -146,8 +146,8 @@ prepareTree dest = do
-- files, which implements exactly the logic that we
-- have for 'alexHappyFiles' above.
alexHappyFiles =
- [ (Stage0, compiler, "CmmParse.y", Just "cmm", "CmmParse.hs")
- , (Stage0, compiler, "CmmLex.x", Just "cmm", "CmmLex.hs")
+ [ (Stage0, compiler, "Parser.y", Just ("GHC" -/- "Cmm"), "Parser.hs")
+ , (Stage0, compiler, "Lexer.x", Just ("GHC" -/- "Cmm"), "Lexer.hs")
, (Stage0, compiler, "Parser.y", Just "parser", "Parser.hs")
, (Stage0, compiler, "Lexer.x", Just "parser", "Lexer.hs")
, (Stage0, hpcBin, "HpcParser.y", Nothing, "HpcParser.hs")
diff --git a/includes/Cmm.h b/includes/Cmm.h
index 546e81e..4e2d1b1 100644
--- a/includes/Cmm.h
+++ b/includes/Cmm.h
@@ -7,7 +7,7 @@
* making .cmm code a bit less error-prone to write, and a bit easier
* on the eye for the reader.
*
- * For the syntax of .cmm files, see the parser in ghc/compiler/cmm/CmmParse.y.
+ * For the syntax of .cmm files, see the parser in ghc/compiler/GHC/Cmm/Parser.y.
*
* Accessing fields of structures defined in the RTS header files is
* done via automatically-generated macros in DerivedConstants.h. For
@@ -469,7 +469,7 @@
// Version of GC_PRIM for use in low-level Cmm. We can call
// stg_gc_prim, because it takes one argument and therefore has a
// platform-independent calling convention (Note [Syntax of .cmm
-// files] in CmmParse.y).
+// files] in GHC.Cmm.Parser).
#define GC_PRIM_LL(fun) \
R1 = fun; \
jump stg_gc_prim [R1];
diff --git a/includes/CodeGen.Platform.hs b/includes/CodeGen.Platform.hs
index b108a61..228e16e 100644
--- a/includes/CodeGen.Platform.hs
+++ b/includes/CodeGen.Platform.hs
@@ -1,5 +1,5 @@
-import CmmExpr
+import GHC.Cmm.Expr
#if !(defined(MACHREGS_i386) || defined(MACHREGS_x86_64) \
|| defined(MACHREGS_sparc) || defined(MACHREGS_powerpc))
import PlainPanic
diff --git a/rts/Apply.cmm b/rts/Apply.cmm
index dcfaa44..f23a507 100644
--- a/rts/Apply.cmm
+++ b/rts/Apply.cmm
@@ -6,7 +6,7 @@
*
* This file is written in a subset of C--, extended with various
* features specific to GHC. It is compiled by GHC directly. For the
- * syntax of .cmm files, see the parser in ghc/compiler/cmm/CmmParse.y.
+ * syntax of .cmm files, see the parser in ghc/compiler/GHC/Cmm/Parser.y.
*
* -------------------------------------------------------------------------- */
diff --git a/rts/Exception.cmm b/rts/Exception.cmm
index 334d0ef..726489e 100644
--- a/rts/Exception.cmm
+++ b/rts/Exception.cmm
@@ -6,7 +6,7 @@
*
* This file is written in a subset of C--, extended with various
* features specific to GHC. It is compiled by GHC directly. For the
- * syntax of .cmm files, see the parser in ghc/compiler/cmm/CmmParse.y.
+ * syntax of .cmm files, see the parser in ghc/compiler/GHC/Cmm/Parser.y.
*
* ---------------------------------------------------------------------------*/
diff --git a/rts/HeapStackCheck.cmm b/rts/HeapStackCheck.cmm
index 85fb1cb..461cf13 100644
--- a/rts/HeapStackCheck.cmm
+++ b/rts/HeapStackCheck.cmm
@@ -6,7 +6,7 @@
*
* This file is written in a subset of C--, extended with various
* features specific to GHC. It is compiled by GHC directly. For the
- * syntax of .cmm files, see the parser in ghc/compiler/cmm/CmmParse.y.
+ * syntax of .cmm files, see the parser in ghc/compiler/GHC/Cmm/Parser.y.
*
* ---------------------------------------------------------------------------*/
diff --git a/rts/PrimOps.cmm b/rts/PrimOps.cmm
index 0486399..7f0b7d5 100644
--- a/rts/PrimOps.cmm
+++ b/rts/PrimOps.cmm
@@ -17,7 +17,7 @@
*
* This file is written in a subset of C--, extended with various
* features specific to GHC. It is compiled by GHC directly. For the
- * syntax of .cmm files, see the parser in ghc/compiler/cmm/CmmParse.y.
+ * syntax of .cmm files, see the parser in ghc/compiler/GHC/Cmm/Parser.y.
*
* ---------------------------------------------------------------------------*/
diff --git a/rts/StgMiscClosures.cmm b/rts/StgMiscClosures.cmm
index 03ea91f..42c7d98 100644
--- a/rts/StgMiscClosures.cmm
+++ b/rts/StgMiscClosures.cmm
@@ -6,7 +6,7 @@
*
* This file is written in a subset of C--, extended with various
* features specific to GHC. It is compiled by GHC directly. For the
- * syntax of .cmm files, see the parser in ghc/compiler/cmm/CmmParse.y.
+ * syntax of .cmm files, see the parser in ghc/compiler/GHC/Cmm/Parser.y.
*
* --------------------------------------------------------------------------*/
diff --git a/rts/StgStartup.cmm b/rts/StgStartup.cmm
index 571e063..122eace 100644
--- a/rts/StgStartup.cmm
+++ b/rts/StgStartup.cmm
@@ -6,7 +6,7 @@
*
* This file is written in a subset of C--, extended with various
* features specific to GHC. It is compiled by GHC directly. For the
- * syntax of .cmm files, see the parser in ghc/compiler/cmm/CmmParse.y.
+ * syntax of .cmm files, see the parser in ghc/compiler/GHC/Cmm/Parser.y.
*
* ---------------------------------------------------------------------------*/
diff --git a/rts/StgStdThunks.cmm b/rts/StgStdThunks.cmm
index 204cd1a..5239496 100644
--- a/rts/StgStdThunks.cmm
+++ b/rts/StgStdThunks.cmm
@@ -6,7 +6,7 @@
*
* This file is written in a subset of C--, extended with various
* features specific to GHC. It is compiled by GHC directly. For the
- * syntax of .cmm files, see the parser in ghc/compiler/cmm/CmmParse.y.
+ * syntax of .cmm files, see the parser in ghc/compiler/GHC/Cmm/Parser.y.
*
* ---------------------------------------------------------------------------*/
diff --git a/rts/Updates.cmm b/rts/Updates.cmm
index 9d00fb8..d459607 100644
--- a/rts/Updates.cmm
+++ b/rts/Updates.cmm
@@ -6,7 +6,7 @@
*
* This file is written in a subset of C--, extended with various
* features specific to GHC. It is compiled by GHC directly. For the
- * syntax of .cmm files, see the parser in ghc/compiler/cmm/CmmParse.y.
+ * syntax of .cmm files, see the parser in ghc/compiler/GHC/Cmm/Parser.y.
*
* ---------------------------------------------------------------------------*/
diff --git a/testsuite/tests/cmm/should_run/HooplPostorder.hs b/testsuite/tests/cmm/should_run/HooplPostorder.hs
index 269efa4..6171c7e 100644
--- a/testsuite/tests/cmm/should_run/HooplPostorder.hs
+++ b/testsuite/tests/cmm/should_run/HooplPostorder.hs
@@ -2,10 +2,10 @@
{-# LANGUAGE KindSignatures #-}
module Main where
-import Hoopl.Block
-import Hoopl.Collections
-import Hoopl.Graph
-import Hoopl.Label
+import GHC.Cmm.Dataflow.Block
+import GHC.Cmm.Dataflow.Collections
+import GHC.Cmm.Dataflow.Graph
+import GHC.Cmm.Dataflow.Label
import Data.Maybe
diff --git a/testsuite/tests/codeGen/should_run/T13825-unit.hs b/testsuite/tests/codeGen/should_run/T13825-unit.hs
index 24fc463..85777bf 100644
--- a/testsuite/tests/codeGen/should_run/T13825-unit.hs
+++ b/testsuite/tests/codeGen/should_run/T13825-unit.hs
@@ -2,7 +2,7 @@ module Main where
import DynFlags
import GHC.Types.RepType
-import SMRep
+import GHC.Runtime.Layout
import GHC.StgToCmm.Layout
import GHC.StgToCmm.Closure
import GHC
diff --git a/testsuite/tests/regalloc/regalloc_unit_tests.hs b/testsuite/tests/regalloc/regalloc_unit_tests.hs
index 5c6d9da..cbd0361 100644
--- a/testsuite/tests/regalloc/regalloc_unit_tests.hs
+++ b/testsuite/tests/regalloc/regalloc_unit_tests.hs
@@ -26,13 +26,13 @@ import qualified X86.Instr
import HscMain
import GHC.StgToCmm.CgUtils
import AsmCodeGen
-import CmmBuildInfoTables
-import CmmPipeline
-import CmmParse
-import CmmInfo
-import Cmm
+import GHC.Cmm.Info.Build
+import GHC.Cmm.Pipeline
+import GHC.Cmm.Parser
+import GHC.Cmm.Info
+import GHC.Cmm
import Module
-import Debug
+import GHC.Cmm.DebugBlock
import GHC
import GhcMonad
import UniqFM