summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSylvain Henry <sylvain@haskus.fr>2019-08-13 17:26:32 +0200
committerSylvain Henry <sylvain@haskus.fr>2019-09-10 00:04:50 +0200
commit447864a94a1679b5b079e08bb7208a0005381cef (patch)
treebaa469c52620ce7ae02def3e5e6a6f109cc89f40
parent270fbe8512f04b6107755fa22bdec62205c0a567 (diff)
downloadhaskell-447864a94a1679b5b079e08bb7208a0005381cef.tar.gz
Module hierarchy: StgToCmm (#13009)
Add StgToCmm module hierarchy. Platform modules that are used in several other places (NCG, LLVM codegen, Cmm transformations) are put into GHC.Platform.
-rw-r--r--compiler/GHC/Platform/ARM.hs (renamed from compiler/codeGen/CodeGen/Platform/ARM.hs)4
-rw-r--r--compiler/GHC/Platform/ARM64.hs (renamed from compiler/codeGen/CodeGen/Platform/ARM64.hs)4
-rw-r--r--compiler/GHC/Platform/NoRegs.hs9
-rw-r--r--compiler/GHC/Platform/PPC.hs (renamed from compiler/codeGen/CodeGen/Platform/PPC.hs)4
-rw-r--r--compiler/GHC/Platform/Regs.hs (renamed from compiler/codeGen/CodeGen/Platform.hs)16
-rw-r--r--compiler/GHC/Platform/SPARC.hs (renamed from compiler/codeGen/CodeGen/Platform/SPARC.hs)4
-rw-r--r--compiler/GHC/Platform/X86.hs (renamed from compiler/codeGen/CodeGen/Platform/X86.hs)4
-rw-r--r--compiler/GHC/Platform/X86_64.hs (renamed from compiler/codeGen/CodeGen/Platform/X86_64.hs)4
-rw-r--r--compiler/GHC/StgToCmm.hs (renamed from compiler/codeGen/StgCmm.hs)22
-rw-r--r--compiler/GHC/StgToCmm/ArgRep.hs (renamed from compiler/codeGen/StgCmmArgRep.hs)12
-rw-r--r--compiler/GHC/StgToCmm/Bind.hs (renamed from compiler/codeGen/StgCmmBind.hs)30
-rw-r--r--compiler/GHC/StgToCmm/Bind.hs-boot (renamed from compiler/codeGen/StgCmmBind.hs-boot)4
-rw-r--r--compiler/GHC/StgToCmm/CgUtils.hs (renamed from compiler/codeGen/CgUtils.hs)4
-rw-r--r--compiler/GHC/StgToCmm/Closure.hs (renamed from compiler/codeGen/StgCmmClosure.hs)10
-rw-r--r--compiler/GHC/StgToCmm/Con.hs (renamed from compiler/codeGen/StgCmmCon.hs)20
-rw-r--r--compiler/GHC/StgToCmm/Env.hs (renamed from compiler/codeGen/StgCmmEnv.hs)10
-rw-r--r--compiler/GHC/StgToCmm/Expr.hs (renamed from compiler/codeGen/StgCmmExpr.hs)36
-rw-r--r--compiler/GHC/StgToCmm/ExtCode.hs (renamed from compiler/codeGen/StgCmmExtCode.hs)6
-rw-r--r--compiler/GHC/StgToCmm/Foreign.hs (renamed from compiler/codeGen/StgCmmForeign.hs)14
-rw-r--r--compiler/GHC/StgToCmm/Heap.hs (renamed from compiler/codeGen/StgCmmHeap.hs)18
-rw-r--r--compiler/GHC/StgToCmm/Hpc.hs (renamed from compiler/codeGen/StgCmmHpc.hs)6
-rw-r--r--compiler/GHC/StgToCmm/Layout.hs (renamed from compiler/codeGen/StgCmmLayout.hs)18
-rw-r--r--compiler/GHC/StgToCmm/Monad.hs (renamed from compiler/codeGen/StgCmmMonad.hs)6
-rw-r--r--compiler/GHC/StgToCmm/Prim.hs (renamed from compiler/codeGen/StgCmmPrim.hs)38
-rw-r--r--compiler/GHC/StgToCmm/Prof.hs (renamed from compiler/codeGen/StgCmmProf.hs)8
-rw-r--r--compiler/GHC/StgToCmm/Ticky.hs (renamed from compiler/codeGen/StgCmmTicky.hs)16
-rw-r--r--compiler/GHC/StgToCmm/Utils.hs (renamed from compiler/codeGen/StgCmmUtils.hs)10
-rw-r--r--compiler/cmm/Cmm.hs4
-rw-r--r--compiler/cmm/CmmBuildInfoTables.hs2
-rw-r--r--compiler/cmm/CmmExpr.hs2
-rw-r--r--compiler/cmm/CmmLayoutStack.hs7
-rw-r--r--compiler/cmm/CmmNode.hs8
-rw-r--r--compiler/cmm/CmmParse.y28
-rw-r--r--compiler/cmm/CmmSink.hs4
-rw-r--r--compiler/cmm/CmmSwitch.hs2
-rw-r--r--compiler/cmm/CmmUtils.hs2
-rw-r--r--compiler/cmm/Debug.hs2
-rw-r--r--compiler/cmm/cmm-notes100
-rw-r--r--compiler/codeGen/CodeGen/Platform/NoRegs.hs9
-rw-r--r--compiler/ghc.cabal.in54
-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/ByteCodeItbls.hs4
-rw-r--r--compiler/ghci/RtClosureInspect.hs4
-rw-r--r--compiler/llvmGen/LlvmCodeGen.hs2
-rw-r--r--compiler/llvmGen/LlvmCodeGen/Base.hs2
-rw-r--r--compiler/llvmGen/LlvmCodeGen/CodeGen.hs2
-rw-r--r--compiler/main/HscMain.hs8
-rw-r--r--compiler/nativeGen/AsmCodeGen.hs2
-rw-r--r--compiler/nativeGen/Dwarf/Types.hs2
-rw-r--r--compiler/nativeGen/PPC/CodeGen.hs2
-rw-r--r--compiler/nativeGen/PPC/Instr.hs2
-rw-r--r--compiler/nativeGen/PPC/Regs.hs2
-rw-r--r--compiler/nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs2
-rw-r--r--compiler/nativeGen/SPARC/CodeGen/Base.hs2
-rw-r--r--compiler/nativeGen/SPARC/Instr.hs2
-rw-r--r--compiler/nativeGen/SPARC/Regs.hs2
-rw-r--r--compiler/nativeGen/X86/CodeGen.hs2
-rw-r--r--compiler/nativeGen/X86/Instr.hs2
-rw-r--r--compiler/nativeGen/X86/Regs.hs2
-rw-r--r--compiler/prelude/PrelRules.hs4
-rw-r--r--compiler/simplStg/StgLiftLams/Analysis.hs20
-rw-r--r--compiler/simplStg/UnariseStg.hs2
-rw-r--r--compiler/stgSyn/StgSyn.hs2
-rw-r--r--docs/stg-spec/stg-spec.mng2
-rw-r--r--includes/rts/prof/CCS.h2
-rw-r--r--includes/rts/storage/FunTypes.h2
-rw-r--r--includes/stg/MiscClosures.h6
-rw-r--r--includes/stg/SMP.h6
-rw-r--r--rts/PrimOps.cmm2
-rw-r--r--testsuite/tests/codeGen/should_run/T13825-unit.hs4
-rw-r--r--testsuite/tests/regalloc/regalloc_unit_tests.hs2
-rw-r--r--utils/genapply/Main.hs2
74 files changed, 285 insertions, 386 deletions
diff --git a/compiler/codeGen/CodeGen/Platform/ARM.hs b/compiler/GHC/Platform/ARM.hs
index a2cb476e04..d0c7e5811a 100644
--- a/compiler/codeGen/CodeGen/Platform/ARM.hs
+++ b/compiler/GHC/Platform/ARM.hs
@@ -1,10 +1,10 @@
{-# LANGUAGE CPP #-}
-module CodeGen.Platform.ARM where
+module GHC.Platform.ARM where
import GhcPrelude
#define MACHREGS_NO_REGS 0
#define MACHREGS_arm 1
-#include "../../../../includes/CodeGen.Platform.hs"
+#include "../../../includes/CodeGen.Platform.hs"
diff --git a/compiler/codeGen/CodeGen/Platform/ARM64.hs b/compiler/GHC/Platform/ARM64.hs
index 6ace181356..ebd66b92c5 100644
--- a/compiler/codeGen/CodeGen/Platform/ARM64.hs
+++ b/compiler/GHC/Platform/ARM64.hs
@@ -1,10 +1,10 @@
{-# LANGUAGE CPP #-}
-module CodeGen.Platform.ARM64 where
+module GHC.Platform.ARM64 where
import GhcPrelude
#define MACHREGS_NO_REGS 0
#define MACHREGS_aarch64 1
-#include "../../../../includes/CodeGen.Platform.hs"
+#include "../../../includes/CodeGen.Platform.hs"
diff --git a/compiler/GHC/Platform/NoRegs.hs b/compiler/GHC/Platform/NoRegs.hs
new file mode 100644
index 0000000000..e8abf44253
--- /dev/null
+++ b/compiler/GHC/Platform/NoRegs.hs
@@ -0,0 +1,9 @@
+{-# LANGUAGE CPP #-}
+
+module GHC.Platform.NoRegs where
+
+import GhcPrelude
+
+#define MACHREGS_NO_REGS 1
+#include "../../../includes/CodeGen.Platform.hs"
+
diff --git a/compiler/codeGen/CodeGen/Platform/PPC.hs b/compiler/GHC/Platform/PPC.hs
index f7eae6b4ca..f405f95438 100644
--- a/compiler/codeGen/CodeGen/Platform/PPC.hs
+++ b/compiler/GHC/Platform/PPC.hs
@@ -1,10 +1,10 @@
{-# LANGUAGE CPP #-}
-module CodeGen.Platform.PPC where
+module GHC.Platform.PPC where
import GhcPrelude
#define MACHREGS_NO_REGS 0
#define MACHREGS_powerpc 1
-#include "../../../../includes/CodeGen.Platform.hs"
+#include "../../../includes/CodeGen.Platform.hs"
diff --git a/compiler/codeGen/CodeGen/Platform.hs b/compiler/GHC/Platform/Regs.hs
index bc216758a0..e7887fbe72 100644
--- a/compiler/codeGen/CodeGen/Platform.hs
+++ b/compiler/GHC/Platform/Regs.hs
@@ -1,5 +1,5 @@
-module CodeGen.Platform
+module GHC.Platform.Regs
(callerSaves, activeStgRegs, haveRegBase, globalRegMaybe, freeReg)
where
@@ -9,13 +9,13 @@ import CmmExpr
import GHC.Platform
import Reg
-import qualified CodeGen.Platform.ARM as ARM
-import qualified CodeGen.Platform.ARM64 as ARM64
-import qualified CodeGen.Platform.PPC as PPC
-import qualified CodeGen.Platform.SPARC as SPARC
-import qualified CodeGen.Platform.X86 as X86
-import qualified CodeGen.Platform.X86_64 as X86_64
-import qualified CodeGen.Platform.NoRegs as NoRegs
+import qualified GHC.Platform.ARM as ARM
+import qualified GHC.Platform.ARM64 as ARM64
+import qualified GHC.Platform.PPC as PPC
+import qualified GHC.Platform.SPARC as SPARC
+import qualified GHC.Platform.X86 as X86
+import qualified GHC.Platform.X86_64 as X86_64
+import qualified GHC.Platform.NoRegs as NoRegs
-- | Returns 'True' if this global register is stored in a caller-saves
-- machine register.
diff --git a/compiler/codeGen/CodeGen/Platform/SPARC.hs b/compiler/GHC/Platform/SPARC.hs
index 5d8dbb1da9..b0cdb27f44 100644
--- a/compiler/codeGen/CodeGen/Platform/SPARC.hs
+++ b/compiler/GHC/Platform/SPARC.hs
@@ -1,10 +1,10 @@
{-# LANGUAGE CPP #-}
-module CodeGen.Platform.SPARC where
+module GHC.Platform.SPARC where
import GhcPrelude
#define MACHREGS_NO_REGS 0
#define MACHREGS_sparc 1
-#include "../../../../includes/CodeGen.Platform.hs"
+#include "../../../includes/CodeGen.Platform.hs"
diff --git a/compiler/codeGen/CodeGen/Platform/X86.hs b/compiler/GHC/Platform/X86.hs
index 84d52c1585..1570ba9fa0 100644
--- a/compiler/codeGen/CodeGen/Platform/X86.hs
+++ b/compiler/GHC/Platform/X86.hs
@@ -1,10 +1,10 @@
{-# LANGUAGE CPP #-}
-module CodeGen.Platform.X86 where
+module GHC.Platform.X86 where
import GhcPrelude
#define MACHREGS_NO_REGS 0
#define MACHREGS_i386 1
-#include "../../../../includes/CodeGen.Platform.hs"
+#include "../../../includes/CodeGen.Platform.hs"
diff --git a/compiler/codeGen/CodeGen/Platform/X86_64.hs b/compiler/GHC/Platform/X86_64.hs
index 1b2b5549ac..d2d1b15c71 100644
--- a/compiler/codeGen/CodeGen/Platform/X86_64.hs
+++ b/compiler/GHC/Platform/X86_64.hs
@@ -1,10 +1,10 @@
{-# LANGUAGE CPP #-}
-module CodeGen.Platform.X86_64 where
+module GHC.Platform.X86_64 where
import GhcPrelude
#define MACHREGS_NO_REGS 0
#define MACHREGS_x86_64 1
-#include "../../../../includes/CodeGen.Platform.hs"
+#include "../../../includes/CodeGen.Platform.hs"
diff --git a/compiler/codeGen/StgCmm.hs b/compiler/GHC/StgToCmm.hs
index 83409b6b24..c7ee604692 100644
--- a/compiler/codeGen/StgCmm.hs
+++ b/compiler/GHC/StgToCmm.hs
@@ -9,22 +9,22 @@
--
-----------------------------------------------------------------------------
-module StgCmm ( codeGen ) where
+module GHC.StgToCmm ( codeGen ) where
#include "HsVersions.h"
import GhcPrelude as Prelude
-import StgCmmProf (initCostCentres, ldvEnter)
-import StgCmmMonad
-import StgCmmEnv
-import StgCmmBind
-import StgCmmCon
-import StgCmmLayout
-import StgCmmUtils
-import StgCmmClosure
-import StgCmmHpc
-import StgCmmTicky
+import GHC.StgToCmm.Prof (initCostCentres, ldvEnter)
+import GHC.StgToCmm.Monad
+import GHC.StgToCmm.Env
+import GHC.StgToCmm.Bind
+import GHC.StgToCmm.Con
+import GHC.StgToCmm.Layout
+import GHC.StgToCmm.Utils
+import GHC.StgToCmm.Closure
+import GHC.StgToCmm.Hpc
+import GHC.StgToCmm.Ticky
import Cmm
import CmmUtils
diff --git a/compiler/codeGen/StgCmmArgRep.hs b/compiler/GHC/StgToCmm/ArgRep.hs
index ef40fce464..cc2fe8306a 100644
--- a/compiler/codeGen/StgCmmArgRep.hs
+++ b/compiler/GHC/StgToCmm/ArgRep.hs
@@ -1,12 +1,12 @@
-----------------------------------------------------------------------------
--
--- Argument representations used in StgCmmLayout.
+-- Argument representations used in GHC.StgToCmm.Layout.
--
-- (c) The University of Glasgow 2013
--
-----------------------------------------------------------------------------
-module StgCmmArgRep (
+module GHC.StgToCmm.ArgRep (
ArgRep(..), toArgRep, argRepSizeW,
argRepString, isNonV, idArgRep,
@@ -17,7 +17,7 @@ module StgCmmArgRep (
import GhcPrelude
-import StgCmmClosure ( idPrimRep )
+import GHC.StgToCmm.Closure ( idPrimRep )
import SMRep ( WordOff )
import Id ( Id )
@@ -30,7 +30,7 @@ import Outputable
import FastString
-- I extricated this code as this new module in order to avoid a
--- cyclic dependency between StgCmmLayout and StgCmmTicky.
+-- cyclic dependency between GHC.StgToCmm.Layout and GHC.StgToCmm.Ticky.
--
-- NSF 18 Feb 2013
@@ -38,7 +38,7 @@ import FastString
-- Classifying arguments: ArgRep
-------------------------------------------------------------------------
--- ArgRep is re-exported by StgCmmLayout, but only for use in the
+-- ArgRep is re-exported by GHC.StgToCmm.Layout, but only for use in the
-- byte-code generator which also needs to know about the
-- classification of arguments.
@@ -108,7 +108,7 @@ idArgRep = toArgRep . idPrimRep
-- This list of argument patterns should be kept in sync with at least
-- the following:
--
--- * StgCmmLayout.stdPattern maybe to some degree?
+-- * GHC.StgToCmm.Layout.stdPattern maybe to some degree?
--
-- * the RTS_RET(stg_ap_*) and RTS_FUN_DECL(stg_ap_*_fast)
-- declarations in includes/stg/MiscClosures.h
diff --git a/compiler/codeGen/StgCmmBind.hs b/compiler/GHC/StgToCmm/Bind.hs
index 7189800f6e..bfe9255783 100644
--- a/compiler/codeGen/StgCmmBind.hs
+++ b/compiler/GHC/StgToCmm/Bind.hs
@@ -6,7 +6,7 @@
--
-----------------------------------------------------------------------------
-module StgCmmBind (
+module GHC.StgToCmm.Bind (
cgTopRhsClosure,
cgBind,
emitBlackHoleCode,
@@ -15,18 +15,18 @@ module StgCmmBind (
import GhcPrelude hiding ((<*>))
-import StgCmmExpr
-import StgCmmMonad
-import StgCmmEnv
-import StgCmmCon
-import StgCmmHeap
-import StgCmmProf (ldvEnterClosure, enterCostCentreFun, enterCostCentreThunk,
+import GHC.StgToCmm.Expr
+import GHC.StgToCmm.Monad
+import GHC.StgToCmm.Env
+import GHC.StgToCmm.Con
+import GHC.StgToCmm.Heap
+import GHC.StgToCmm.Prof (ldvEnterClosure, enterCostCentreFun, enterCostCentreThunk,
initUpdFrameProf)
-import StgCmmTicky
-import StgCmmLayout
-import StgCmmUtils
-import StgCmmClosure
-import StgCmmForeign (emitPrimCall)
+import GHC.StgToCmm.Ticky
+import GHC.StgToCmm.Layout
+import GHC.StgToCmm.Utils
+import GHC.StgToCmm.Closure
+import GHC.StgToCmm.Foreign (emitPrimCall)
import MkGraph
import CoreSyn ( AltCon(..), tickishIsCode )
@@ -208,7 +208,7 @@ cgRhs id (StgRhsCon cc con args)
-- con args are always non-void,
-- see Note [Post-unarisation invariants] in UnariseStg
-{- See Note [GC recovery] in compiler/codeGen/StgCmmClosure.hs -}
+{- See Note [GC recovery] in compiler/GHC.StgToCmm/Closure.hs -}
cgRhs id (StgRhsClosure fvs cc upd_flag args body)
= do dflags <- getDynFlags
mkRhsClosure dflags id cc (nonVoidIds (dVarSetElems fvs)) upd_flag args body
@@ -299,7 +299,7 @@ mkRhsClosure dflags bndr _cc
[] -- No args; a thunk
(StgApp fun_id args)
- -- We are looking for an "ApThunk"; see data con ApThunk in StgCmmClosure
+ -- We are looking for an "ApThunk"; see data con ApThunk in GHC.StgToCmm.Closure
-- of form (x1 x2 .... xn), where all the xi are locals (not top-level)
-- So the xi will all be free variables
| args `lengthIs` (n_fvs-1) -- This happens only if the fun_id and
@@ -488,7 +488,7 @@ closureCodeBody top_lvl bndr cl_info cc args arity body fv_details
; loop_header_id <- newBlockId
-- Extend reader monad with information that
-- self-recursive tail calls can be optimized into local
- -- jumps. See Note [Self-recursive tail calls] in StgCmmExpr.
+ -- jumps. See Note [Self-recursive tail calls] in GHC.StgToCmm.Expr.
; withSelfLoop (bndr, loop_header_id, arg_regs) $ do
{
-- Main payload
diff --git a/compiler/codeGen/StgCmmBind.hs-boot b/compiler/GHC/StgToCmm/Bind.hs-boot
index 8e3dd38ad8..d16c34ebd3 100644
--- a/compiler/codeGen/StgCmmBind.hs-boot
+++ b/compiler/GHC/StgToCmm/Bind.hs-boot
@@ -1,6 +1,6 @@
-module StgCmmBind where
+module GHC.StgToCmm.Bind where
-import StgCmmMonad( FCode )
+import GHC.StgToCmm.Monad( FCode )
import StgSyn( CgStgBinding )
cgBind :: CgStgBinding -> FCode ()
diff --git a/compiler/codeGen/CgUtils.hs b/compiler/GHC/StgToCmm/CgUtils.hs
index 0ff9bd8b56..f3dccd9745 100644
--- a/compiler/codeGen/CgUtils.hs
+++ b/compiler/GHC/StgToCmm/CgUtils.hs
@@ -8,7 +8,7 @@
--
-----------------------------------------------------------------------------
-module CgUtils (
+module GHC.StgToCmm.CgUtils (
fixStgRegisters,
baseRegOffset,
get_Regtable_addr_from_offset,
@@ -18,7 +18,7 @@ module CgUtils (
import GhcPrelude
-import CodeGen.Platform
+import GHC.Platform.Regs
import Cmm
import Hoopl.Block
import Hoopl.Graph
diff --git a/compiler/codeGen/StgCmmClosure.hs b/compiler/GHC/StgToCmm/Closure.hs
index ac8db1268f..b56b06f399 100644
--- a/compiler/codeGen/StgCmmClosure.hs
+++ b/compiler/GHC/StgToCmm/Closure.hs
@@ -11,7 +11,7 @@
--
-----------------------------------------------------------------------------
-module StgCmmClosure (
+module GHC.StgToCmm.Closure (
DynTag, tagForCon, isSmallFamily,
idPrimRep, isVoidRep, isGcPtrRep, addIdReps, addArgReps,
@@ -97,9 +97,9 @@ import qualified Data.ByteString.Char8 as BS8
-- Data types and synonyms
-----------------------------------------------------------------------------
--- These data types are mostly used by other modules, especially StgCmmMonad,
--- but we define them here because some functions in this module need to
--- have access to them as well
+-- These data types are mostly used by other modules, especially
+-- GHC.StgToCmm.Monad, but we define them here because some functions in this
+-- module need to have access to them as well
data CgLoc
= CmmLoc CmmExpr -- A stable CmmExpr; that is, one not mentioning
@@ -566,7 +566,7 @@ getCallMethod dflags _ id _ n_args v_args _cg_loc
-- * function is performing a self-recursive call in a tail position
-- * number of non-void parameters of the function matches functions arity.
-- See Note [Self-recursive tail calls] and Note [Void arguments in
- -- self-recursive tail calls] in StgCmmExpr for more details
+ -- self-recursive tail calls] in GHC.StgToCmm.Expr for more details
= JumpToIt block_id args
getCallMethod dflags name id (LFReEntrant _ _ arity _ _) n_args _v_args _cg_loc
diff --git a/compiler/codeGen/StgCmmCon.hs b/compiler/GHC/StgToCmm/Con.hs
index 67a9776eac..08508fbecc 100644
--- a/compiler/codeGen/StgCmmCon.hs
+++ b/compiler/GHC/StgToCmm/Con.hs
@@ -4,14 +4,14 @@
--
-- Stg to C--: code generation for constructors
--
--- This module provides the support code for StgCmm to deal with with
+-- This module provides the support code for StgToCmm to deal with with
-- constructors on the RHSs of let(rec)s.
--
-- (c) The University of Glasgow 2004-2006
--
-----------------------------------------------------------------------------
-module StgCmmCon (
+module GHC.StgToCmm.Con (
cgTopRhsCon, buildDynCon, bindConArgs
) where
@@ -22,12 +22,12 @@ import GhcPrelude
import StgSyn
import CoreSyn ( AltCon(..) )
-import StgCmmMonad
-import StgCmmEnv
-import StgCmmHeap
-import StgCmmLayout
-import StgCmmUtils
-import StgCmmClosure
+import GHC.StgToCmm.Monad
+import GHC.StgToCmm.Env
+import GHC.StgToCmm.Heap
+import GHC.StgToCmm.Layout
+import GHC.StgToCmm.Utils
+import GHC.StgToCmm.Closure
import CmmExpr
import CmmUtils
@@ -89,7 +89,7 @@ cgTopRhsCon dflags id con args =
amode <- getArgAmode arg
case amode of
CmmLit lit -> return lit
- _ -> panic "StgCmmCon.cgTopRhsCon"
+ _ -> panic "GHC.StgToCmm.Con.cgTopRhsCon"
nonptr_wds = tot_wds - ptr_wds
@@ -272,7 +272,7 @@ bindConArgs (DataAlt con) base args
-- when accessing the constructor field.
bind_arg :: (NonVoid Id, ByteOff) -> FCode (Maybe LocalReg)
bind_arg (arg@(NonVoid b), offset)
- | isDeadBinder b -- See Note [Dead-binder optimisation] in StgCmmExpr
+ | isDeadBinder b -- See Note [Dead-binder optimisation] in GHC.StgToCmm.Expr
= return Nothing
| otherwise
= do { emit $ mkTaggedObjectLoad dflags (idToReg dflags arg)
diff --git a/compiler/codeGen/StgCmmEnv.hs b/compiler/GHC/StgToCmm/Env.hs
index e605762f1f..e32c6a1ecb 100644
--- a/compiler/codeGen/StgCmmEnv.hs
+++ b/compiler/GHC/StgToCmm/Env.hs
@@ -7,7 +7,7 @@
-- (c) The University of Glasgow 2004-2006
--
-----------------------------------------------------------------------------
-module StgCmmEnv (
+module GHC.StgToCmm.Env (
CgIdInfo,
litIdInfo, lneIdInfo, rhsIdInfo, mkRhsInit,
@@ -27,9 +27,9 @@ module StgCmmEnv (
import GhcPrelude
import TyCon
-import StgCmmMonad
-import StgCmmUtils
-import StgCmmClosure
+import GHC.StgToCmm.Monad
+import GHC.StgToCmm.Utils
+import GHC.StgToCmm.Closure
import CLabel
@@ -146,7 +146,7 @@ getCgIdInfo id
cgLookupPanic :: Id -> FCode a
cgLookupPanic id
= do local_binds <- getBinds
- pprPanic "StgCmmEnv: variable not found"
+ pprPanic "GHC.StgToCmm.Env: variable not found"
(vcat [ppr id,
text "local binds for:",
pprUFM local_binds $ \infos ->
diff --git a/compiler/codeGen/StgCmmExpr.hs b/compiler/GHC/StgToCmm/Expr.hs
index 70a044a7ab..59cd246441 100644
--- a/compiler/codeGen/StgCmmExpr.hs
+++ b/compiler/GHC/StgToCmm/Expr.hs
@@ -8,25 +8,25 @@
--
-----------------------------------------------------------------------------
-module StgCmmExpr ( cgExpr ) where
+module GHC.StgToCmm.Expr ( cgExpr ) where
#include "HsVersions.h"
import GhcPrelude hiding ((<*>))
-import {-# SOURCE #-} StgCmmBind ( cgBind )
+import {-# SOURCE #-} GHC.StgToCmm.Bind ( cgBind )
-import StgCmmMonad
-import StgCmmHeap
-import StgCmmEnv
-import StgCmmCon
-import StgCmmProf (saveCurrentCostCentre, restoreCurrentCostCentre, emitSetCCC)
-import StgCmmLayout
-import StgCmmPrim
-import StgCmmHpc
-import StgCmmTicky
-import StgCmmUtils
-import StgCmmClosure
+import GHC.StgToCmm.Monad
+import GHC.StgToCmm.Heap
+import GHC.StgToCmm.Env
+import GHC.StgToCmm.Con
+import GHC.StgToCmm.Prof (saveCurrentCostCentre, restoreCurrentCostCentre, emitSetCCC)
+import GHC.StgToCmm.Layout
+import GHC.StgToCmm.Prim
+import GHC.StgToCmm.Hpc
+import GHC.StgToCmm.Ticky
+import GHC.StgToCmm.Utils
+import GHC.StgToCmm.Closure
import StgSyn
@@ -552,9 +552,9 @@ check will reset the heap usage. Slop in the heap breaks LDV profiling
Note [Inlining out-of-line primops and heap checks]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-If shouldInlinePrimOp returns True when called from StgCmmExpr for the
+If shouldInlinePrimOp returns True when called from GHC.StgToCmm.Expr for the
purpose of heap check placement, we *must* inline the primop later in
-StgCmmPrim. If we don't things will go wrong.
+GHC.StgToCmm.Prim. If we don't things will go wrong.
-}
-----------------
@@ -851,18 +851,18 @@ cgIdApp fun_id args = do
--
-- * Whenever we are compiling a function, we set that information to reflect
-- the fact that function currently being compiled can be jumped to, instead
--- of called. This is done in closureCodyBody in StgCmmBind.
+-- of called. This is done in closureCodyBody in GHC.StgToCmm.Bind.
--
-- * We also have to emit a label to which we will be jumping. We make sure
-- that the label is placed after a stack check but before the heap
-- check. The reason is that making a recursive tail-call does not increase
-- the stack so we only need to check once. But it may grow the heap, so we
-- have to repeat the heap check in every self-call. This is done in
--- do_checks in StgCmmHeap.
+-- do_checks in GHC.StgToCmm.Heap.
--
-- * When we begin compilation of another closure we remove the additional
-- information from the environment. This is done by forkClosureBody
--- in StgCmmMonad. Other functions that duplicate the environment -
+-- in GHC.StgToCmm.Monad. Other functions that duplicate the environment -
-- forkLneBody, forkAlts, codeOnly - duplicate that information. In other
-- words, we only need to clean the environment of the self-loop information
-- when compiling right hand side of a closure (binding).
diff --git a/compiler/codeGen/StgCmmExtCode.hs b/compiler/GHC/StgToCmm/ExtCode.hs
index 1d35c3454e..be2592edd3 100644
--- a/compiler/codeGen/StgCmmExtCode.hs
+++ b/compiler/GHC/StgToCmm/ExtCode.hs
@@ -10,7 +10,7 @@
-- to collect declarations as we parse the proc, and feed the environment
-- back in circularly (to avoid a two-pass algorithm).
-module StgCmmExtCode (
+module GHC.StgToCmm.ExtCode (
CmmParse, unEC,
Named(..), Env,
@@ -39,8 +39,8 @@ where
import GhcPrelude
-import qualified StgCmmMonad as F
-import StgCmmMonad (FCode, newUnique)
+import qualified GHC.StgToCmm.Monad as F
+import GHC.StgToCmm.Monad (FCode, newUnique)
import Cmm
import CLabel
diff --git a/compiler/codeGen/StgCmmForeign.hs b/compiler/GHC/StgToCmm/Foreign.hs
index 172dcba219..dacaff41ba 100644
--- a/compiler/codeGen/StgCmmForeign.hs
+++ b/compiler/GHC/StgToCmm/Foreign.hs
@@ -6,7 +6,7 @@
--
-----------------------------------------------------------------------------
-module StgCmmForeign (
+module GHC.StgToCmm.Foreign (
cgForeignCall,
emitPrimCall, emitCCall,
emitForeignCall, -- For CmmParse
@@ -21,12 +21,12 @@ module StgCmmForeign (
import GhcPrelude hiding( succ, (<*>) )
import StgSyn
-import StgCmmProf (storeCurCCS, ccsType)
-import StgCmmEnv
-import StgCmmMonad
-import StgCmmUtils
-import StgCmmClosure
-import StgCmmLayout
+import GHC.StgToCmm.Prof (storeCurCCS, ccsType)
+import GHC.StgToCmm.Env
+import GHC.StgToCmm.Monad
+import GHC.StgToCmm.Utils
+import GHC.StgToCmm.Closure
+import GHC.StgToCmm.Layout
import BlockId (newBlockId)
import Cmm
diff --git a/compiler/codeGen/StgCmmHeap.hs b/compiler/GHC/StgToCmm/Heap.hs
index da9e85f1e7..a1f016c13c 100644
--- a/compiler/codeGen/StgCmmHeap.hs
+++ b/compiler/GHC/StgToCmm/Heap.hs
@@ -6,7 +6,7 @@
--
-----------------------------------------------------------------------------
-module StgCmmHeap (
+module GHC.StgToCmm.Heap (
getVirtHp, setVirtHp, setRealHp,
getHpRelOffset,
@@ -24,13 +24,13 @@ import GhcPrelude hiding ((<*>))
import StgSyn
import CLabel
-import StgCmmLayout
-import StgCmmUtils
-import StgCmmMonad
-import StgCmmProf (profDynAlloc, dynProfHdr, staticProfHdr)
-import StgCmmTicky
-import StgCmmClosure
-import StgCmmEnv
+import GHC.StgToCmm.Layout
+import GHC.StgToCmm.Utils
+import GHC.StgToCmm.Monad
+import GHC.StgToCmm.Prof (profDynAlloc, dynProfHdr, staticProfHdr)
+import GHC.StgToCmm.Ticky
+import GHC.StgToCmm.Closure
+import GHC.StgToCmm.Env
import MkGraph
@@ -659,7 +659,7 @@ do_checks mb_stk_hwm checkYield mb_alloc_lit do_gc = do
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
--
-- Self-recursive loop header is required by loopification optimization (See
--- Note [Self-recursive tail calls] in StgCmmExpr). We emit it if:
+-- Note [Self-recursive tail calls] in GHC.StgToCmm.Expr). We emit it if:
--
-- 1. There is information about self-loop in the FCode environment. We don't
-- check the binder (first component of the self_loop_info) because we are
diff --git a/compiler/codeGen/StgCmmHpc.hs b/compiler/GHC/StgToCmm/Hpc.hs
index 8e9676bd33..e33d39245c 100644
--- a/compiler/codeGen/StgCmmHpc.hs
+++ b/compiler/GHC/StgToCmm/Hpc.hs
@@ -6,18 +6,18 @@
--
-----------------------------------------------------------------------------
-module StgCmmHpc ( initHpc, mkTickBox ) where
+module GHC.StgToCmm.Hpc ( initHpc, mkTickBox ) where
import GhcPrelude
-import StgCmmMonad
+import GHC.StgToCmm.Monad
import MkGraph
import CmmExpr
import CLabel
import Module
import CmmUtils
-import StgCmmUtils
+import GHC.StgToCmm.Utils
import HscTypes
import DynFlags
diff --git a/compiler/codeGen/StgCmmLayout.hs b/compiler/GHC/StgToCmm/Layout.hs
index 78a7cf3f85..f4834376ed 100644
--- a/compiler/codeGen/StgCmmLayout.hs
+++ b/compiler/GHC/StgToCmm/Layout.hs
@@ -9,7 +9,7 @@
--
-----------------------------------------------------------------------------
-module StgCmmLayout (
+module GHC.StgToCmm.Layout (
mkArgDescr,
emitCall, emitReturn, adjustHpBackwards,
@@ -26,7 +26,7 @@ module StgCmmLayout (
mkVirtConstrSizes,
getHpRelOffset,
- ArgRep(..), toArgRep, argRepSizeW -- re-exported from StgCmmArgRep
+ ArgRep(..), toArgRep, argRepSizeW -- re-exported from GHC.StgToCmm.ArgRep
) where
@@ -34,12 +34,12 @@ module StgCmmLayout (
import GhcPrelude hiding ((<*>))
-import StgCmmClosure
-import StgCmmEnv
-import StgCmmArgRep -- notably: ( slowCallPattern )
-import StgCmmTicky
-import StgCmmMonad
-import StgCmmUtils
+import GHC.StgToCmm.Closure
+import GHC.StgToCmm.Env
+import GHC.StgToCmm.ArgRep -- notably: ( slowCallPattern )
+import GHC.StgToCmm.Ticky
+import GHC.StgToCmm.Monad
+import GHC.StgToCmm.Utils
import MkGraph
import SMRep
@@ -387,7 +387,7 @@ hpRel :: VirtualHpOffset -- virtual offset of Hp
hpRel hp off = off - hp
getHpRelOffset :: VirtualHpOffset -> FCode CmmExpr
--- See Note [Virtual and real heap pointers] in StgCmmMonad
+-- See Note [Virtual and real heap pointers] in GHC.StgToCmm.Monad
getHpRelOffset virtual_offset
= do dflags <- getDynFlags
hp_usg <- getHpUsage
diff --git a/compiler/codeGen/StgCmmMonad.hs b/compiler/GHC/StgToCmm/Monad.hs
index d6f84c6a0a..716cbdab78 100644
--- a/compiler/codeGen/StgCmmMonad.hs
+++ b/compiler/GHC/StgToCmm/Monad.hs
@@ -9,7 +9,7 @@
--
-----------------------------------------------------------------------------
-module StgCmmMonad (
+module GHC.StgToCmm.Monad (
FCode, -- type
initC, runC, fixC,
@@ -62,7 +62,7 @@ module StgCmmMonad (
import GhcPrelude hiding( sequence, succ )
import Cmm
-import StgCmmClosure
+import GHC.StgToCmm.Closure
import DynFlags
import Hoopl.Collections
import MkGraph
@@ -164,7 +164,7 @@ data CgInfoDownwards -- information only passed *downwards* by the monad
cgd_self_loop :: Maybe SelfLoopInfo,-- Which tail calls can be compiled
-- as local jumps? See Note
-- [Self-recursive tail calls] in
- -- StgCmmExpr
+ -- GHC.StgToCmm.Expr
cgd_tick_scope:: CmmTickScope -- Tick scope for new blocks & ticks
}
diff --git a/compiler/codeGen/StgCmmPrim.hs b/compiler/GHC/StgToCmm/Prim.hs
index 61d88feabb..dc69a51916 100644
--- a/compiler/codeGen/StgCmmPrim.hs
+++ b/compiler/GHC/StgToCmm/Prim.hs
@@ -10,7 +10,7 @@
--
-----------------------------------------------------------------------------
-module StgCmmPrim (
+module GHC.StgToCmm.Prim (
cgOpApp,
cgPrimOp, -- internal(ish), used by cgCase to get code for a
-- comparison without also turning it into a Bool.
@@ -21,14 +21,14 @@ module StgCmmPrim (
import GhcPrelude hiding ((<*>))
-import StgCmmLayout
-import StgCmmForeign
-import StgCmmEnv
-import StgCmmMonad
-import StgCmmUtils
-import StgCmmTicky
-import StgCmmHeap
-import StgCmmProf ( costCentreFrom )
+import GHC.StgToCmm.Layout
+import GHC.StgToCmm.Foreign
+import GHC.StgToCmm.Env
+import GHC.StgToCmm.Monad
+import GHC.StgToCmm.Utils
+import GHC.StgToCmm.Ticky
+import GHC.StgToCmm.Heap
+import GHC.StgToCmm.Prof ( costCentreFrom )
import DynFlags
import GHC.Platform
@@ -1578,7 +1578,7 @@ doIndexOffAddrOp :: Maybe MachOp
doIndexOffAddrOp maybe_post_read_cast rep [res] [addr,idx]
= mkBasicIndexedRead 0 maybe_post_read_cast rep res addr rep idx
doIndexOffAddrOp _ _ _ _
- = panic "StgCmmPrim: doIndexOffAddrOp"
+ = panic "GHC.StgToCmm.Prim: doIndexOffAddrOp"
doIndexOffAddrOpAs :: Maybe MachOp
-> CmmType
@@ -1589,7 +1589,7 @@ doIndexOffAddrOpAs :: Maybe MachOp
doIndexOffAddrOpAs maybe_post_read_cast rep idx_rep [res] [addr,idx]
= mkBasicIndexedRead 0 maybe_post_read_cast rep res addr idx_rep idx
doIndexOffAddrOpAs _ _ _ _ _
- = panic "StgCmmPrim: doIndexOffAddrOpAs"
+ = panic "GHC.StgToCmm.Prim: doIndexOffAddrOpAs"
doIndexByteArrayOp :: Maybe MachOp
-> CmmType
@@ -1600,7 +1600,7 @@ doIndexByteArrayOp maybe_post_read_cast rep [res] [addr,idx]
= do dflags <- getDynFlags
mkBasicIndexedRead (arrWordsHdrSize dflags) maybe_post_read_cast rep res addr rep idx
doIndexByteArrayOp _ _ _ _
- = panic "StgCmmPrim: doIndexByteArrayOp"
+ = panic "GHC.StgToCmm.Prim: doIndexByteArrayOp"
doIndexByteArrayOpAs :: Maybe MachOp
-> CmmType
@@ -1612,7 +1612,7 @@ doIndexByteArrayOpAs maybe_post_read_cast rep idx_rep [res] [addr,idx]
= do dflags <- getDynFlags
mkBasicIndexedRead (arrWordsHdrSize dflags) maybe_post_read_cast rep res addr idx_rep idx
doIndexByteArrayOpAs _ _ _ _ _
- = panic "StgCmmPrim: doIndexByteArrayOpAs"
+ = panic "GHC.StgToCmm.Prim: doIndexByteArrayOpAs"
doReadPtrArrayOp :: LocalReg
-> CmmExpr
@@ -1630,7 +1630,7 @@ doWriteOffAddrOp :: Maybe MachOp
doWriteOffAddrOp maybe_pre_write_cast idx_ty [] [addr,idx,val]
= mkBasicIndexedWrite 0 maybe_pre_write_cast addr idx_ty idx val
doWriteOffAddrOp _ _ _ _
- = panic "StgCmmPrim: doWriteOffAddrOp"
+ = panic "GHC.StgToCmm.Prim: doWriteOffAddrOp"
doWriteByteArrayOp :: Maybe MachOp
-> CmmType
@@ -1641,7 +1641,7 @@ doWriteByteArrayOp maybe_pre_write_cast idx_ty [] [addr,idx,val]
= do dflags <- getDynFlags
mkBasicIndexedWrite (arrWordsHdrSize dflags) maybe_pre_write_cast addr idx_ty idx val
doWriteByteArrayOp _ _ _ _
- = panic "StgCmmPrim: doWriteByteArrayOp"
+ = panic "GHC.StgToCmm.Prim: doWriteByteArrayOp"
doWritePtrArrayOp :: CmmExpr
-> CmmExpr
@@ -1932,7 +1932,7 @@ doPrefetchByteArrayOp locality [addr,idx]
= do dflags <- getDynFlags
mkBasicPrefetch locality (arrWordsHdrSize dflags) addr idx
doPrefetchByteArrayOp _ _
- = panic "StgCmmPrim: doPrefetchByteArrayOp"
+ = panic "GHC.StgToCmm.Prim: doPrefetchByteArrayOp"
-- | Translate mutable byte array prefetch operations into proper primcalls.
doPrefetchMutableByteArrayOp :: Int
@@ -1942,7 +1942,7 @@ doPrefetchMutableByteArrayOp locality [addr,idx]
= do dflags <- getDynFlags
mkBasicPrefetch locality (arrWordsHdrSize dflags) addr idx
doPrefetchMutableByteArrayOp _ _
- = panic "StgCmmPrim: doPrefetchByteArrayOp"
+ = panic "GHC.StgToCmm.Prim: doPrefetchByteArrayOp"
-- | Translate address prefetch operations into proper primcalls.
doPrefetchAddrOp ::Int
@@ -1951,7 +1951,7 @@ doPrefetchAddrOp ::Int
doPrefetchAddrOp locality [addr,idx]
= mkBasicPrefetch locality 0 addr idx
doPrefetchAddrOp _ _
- = panic "StgCmmPrim: doPrefetchAddrOp"
+ = panic "GHC.StgToCmm.Prim: doPrefetchAddrOp"
-- | Translate value prefetch operations into proper primcalls.
doPrefetchValueOp :: Int
@@ -1961,7 +1961,7 @@ doPrefetchValueOp locality [addr]
= do dflags <- getDynFlags
mkBasicPrefetch locality 0 addr (CmmLit (CmmInt 0 (wordWidth dflags)))
doPrefetchValueOp _ _
- = panic "StgCmmPrim: doPrefetchValueOp"
+ = panic "GHC.StgToCmm.Prim: doPrefetchValueOp"
-- | helper to generate prefetch primcalls
mkBasicPrefetch :: Int -- Locality level 0-3
diff --git a/compiler/codeGen/StgCmmProf.hs b/compiler/GHC/StgToCmm/Prof.hs
index 172b77c8f9..ce8ef61f17 100644
--- a/compiler/codeGen/StgCmmProf.hs
+++ b/compiler/GHC/StgToCmm/Prof.hs
@@ -6,7 +6,7 @@
--
-----------------------------------------------------------------------------
-module StgCmmProf (
+module GHC.StgToCmm.Prof (
initCostCentres, ccType, ccsType,
mkCCostCentre, mkCCostCentreStack,
@@ -25,9 +25,9 @@ module StgCmmProf (
import GhcPrelude
-import StgCmmClosure
-import StgCmmUtils
-import StgCmmMonad
+import GHC.StgToCmm.Closure
+import GHC.StgToCmm.Utils
+import GHC.StgToCmm.Monad
import SMRep
import MkGraph
diff --git a/compiler/codeGen/StgCmmTicky.hs b/compiler/GHC/StgToCmm/Ticky.hs
index 868b52f402..06ef520c0d 100644
--- a/compiler/codeGen/StgCmmTicky.hs
+++ b/compiler/GHC/StgToCmm/Ticky.hs
@@ -65,7 +65,7 @@ the code generator as well as the RTS because:
-}
-module StgCmmTicky (
+module GHC.StgToCmm.Ticky (
withNewTickyCounterFun,
withNewTickyCounterLNE,
withNewTickyCounterThunk,
@@ -106,10 +106,10 @@ module StgCmmTicky (
import GhcPrelude
-import StgCmmArgRep ( slowCallPattern , toArgRep , argRepString )
-import StgCmmClosure
-import StgCmmUtils
-import StgCmmMonad
+import GHC.StgToCmm.ArgRep ( slowCallPattern , toArgRep , argRepString )
+import GHC.StgToCmm.Closure
+import GHC.StgToCmm.Utils
+import GHC.StgToCmm.Monad
import StgSyn
import CmmExpr
@@ -433,7 +433,7 @@ calls.
Nowadays, though (ie as of the eval/apply paper), the significantly
slower calls are actually just a subset of these: the ones with no
-built-in argument pattern (cf StgCmmArgRep.slowCallPattern)
+built-in argument pattern (cf GHC.StgToCmm.ArgRep.slowCallPattern)
So for ticky profiling, we split slow calls into
"SLOW_CALL_fast_<pattern>_ctr" (those matching a built-in pattern) and
@@ -486,7 +486,7 @@ tickyDynAlloc mb_id rep lf = ifTicky $ getDynFlags >>= \dflags ->
tickyAllocHeap ::
Bool -> -- is this a genuine allocation? As opposed to
- -- StgCmmLayout.adjustHpBackwards
+ -- GHC.StgToCmm.Layout.adjustHpBackwards
VirtualHpOffset -> FCode ()
-- Called when doing a heap check [TICK_ALLOC_HEAP]
-- Must be lazy in the amount of allocation!
@@ -497,7 +497,7 @@ tickyAllocHeap genuine hp
; emit $ catAGraphs $
-- only test hp from within the emit so that the monadic
-- computation itself is not strict in hp (cf knot in
- -- StgCmmMonad.getHeapUsage)
+ -- GHC.StgToCmm.Monad.getHeapUsage)
if hp == 0 then []
else let !bytes = wORD_SIZE dflags * hp in [
-- Bump the allocation total in the closure's StgEntCounter
diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/GHC/StgToCmm/Utils.hs
index 766584e2c9..30e37bb930 100644
--- a/compiler/codeGen/StgCmmUtils.hs
+++ b/compiler/GHC/StgToCmm/Utils.hs
@@ -8,7 +8,7 @@
--
-----------------------------------------------------------------------------
-module StgCmmUtils (
+module GHC.StgToCmm.Utils (
cgLit, mkSimpleLit,
emitDataLits, mkDataLits,
emitRODataLits, mkRODataLits,
@@ -45,16 +45,16 @@ module StgCmmUtils (
import GhcPrelude
-import StgCmmMonad
-import StgCmmClosure
+import GHC.StgToCmm.Monad
+import GHC.StgToCmm.Closure
import Cmm
import BlockId
import MkGraph
-import CodeGen.Platform
+import GHC.Platform.Regs
import CLabel
import CmmUtils
import CmmSwitch
-import CgUtils
+import GHC.StgToCmm.CgUtils
import ForeignCall
import IdInfo
diff --git a/compiler/cmm/Cmm.hs b/compiler/cmm/Cmm.hs
index 60fe874b2f..3a6c0af697 100644
--- a/compiler/cmm/Cmm.hs
+++ b/compiler/cmm/Cmm.hs
@@ -120,8 +120,8 @@ data CmmStackInfo
= StackInfo {
arg_space :: ByteOff,
-- number of bytes of arguments on the stack on entry to the
- -- the proc. This is filled in by StgCmm.codeGen, and used
- -- by the stack allocator later.
+ -- the proc. This is filled in by GHC.StgToCmm.codeGen, and
+ -- used by the stack allocator later.
updfr_space :: Maybe ByteOff,
-- XXX: this never contains anything useful, but it should.
-- See comment in CmmLayoutStack.
diff --git a/compiler/cmm/CmmBuildInfoTables.hs b/compiler/cmm/CmmBuildInfoTables.hs
index bde52de3af..9dc66a44e1 100644
--- a/compiler/cmm/CmmBuildInfoTables.hs
+++ b/compiler/cmm/CmmBuildInfoTables.hs
@@ -27,7 +27,7 @@ import Outputable
import SMRep
import UniqSupply
import CostCentre
-import StgCmmHeap
+import GHC.StgToCmm.Heap
import Control.Monad
import Data.Map (Map)
diff --git a/compiler/cmm/CmmExpr.hs b/compiler/cmm/CmmExpr.hs
index 901df5d908..860ee1a7f5 100644
--- a/compiler/cmm/CmmExpr.hs
+++ b/compiler/cmm/CmmExpr.hs
@@ -598,7 +598,7 @@ globalRegType _ (DoubleReg _) = cmmFloat W64
globalRegType _ (LongReg _) = cmmBits W64
-- TODO: improve the internal model of SIMD/vectorized registers
-- the right design SHOULd improve handling of float and double code too.
--- see remarks in "NOTE [SIMD Design for the future]"" in StgCmmPrim
+-- see remarks in "NOTE [SIMD Design for the future]"" in GHC.StgToCmm.Prim
globalRegType _ (XmmReg _) = cmmVec 4 (cmmBits W32)
globalRegType _ (YmmReg _) = cmmVec 8 (cmmBits W32)
globalRegType _ (ZmmReg _) = cmmVec 16 (cmmBits W32)
diff --git a/compiler/cmm/CmmLayoutStack.hs b/compiler/cmm/CmmLayoutStack.hs
index 3b3f49e20b..e26f2878c0 100644
--- a/compiler/cmm/CmmLayoutStack.hs
+++ b/compiler/cmm/CmmLayoutStack.hs
@@ -5,8 +5,8 @@ module CmmLayoutStack (
import GhcPrelude hiding ((<*>))
-import StgCmmUtils ( callerSaveVolatileRegs ) -- XXX layering violation
-import StgCmmForeign ( saveThreadState, loadThreadState ) -- XXX layering violation
+import GHC.StgToCmm.Utils ( callerSaveVolatileRegs, newTemp ) -- XXX layering violation
+import GHC.StgToCmm.Foreign ( saveThreadState, loadThreadState ) -- XXX layering violation
import BasicTypes
import Cmm
@@ -25,7 +25,6 @@ import Hoopl.Dataflow
import Hoopl.Graph
import Hoopl.Label
import UniqSupply
-import StgCmmUtils ( newTemp )
import Maybes
import UniqFM
import Util
@@ -918,7 +917,7 @@ areaToSp dflags sp_old _sp_hwm area_off (CmmStackSlot area n)
areaToSp dflags _ sp_hwm _ (CmmLit CmmHighStackMark)
= mkIntExpr dflags sp_hwm
-- Replace CmmHighStackMark with the number of bytes of stack used,
- -- the sp_hwm. See Note [Stack usage] in StgCmmHeap
+ -- the sp_hwm. See Note [Stack usage] in GHC.StgToCmm.Heap
areaToSp dflags _ _ _ (CmmMachOp (MO_U_Lt _) args)
| falseStackCheck args
diff --git a/compiler/cmm/CmmNode.hs b/compiler/cmm/CmmNode.hs
index 988610fda4..9d6fa7f29b 100644
--- a/compiler/cmm/CmmNode.hs
+++ b/compiler/cmm/CmmNode.hs
@@ -26,7 +26,7 @@ module CmmNode (
import GhcPrelude hiding (succ)
-import CodeGen.Platform
+import GHC.Platform.Regs
import CmmExpr
import CmmSwitch
import DynFlags
@@ -90,7 +90,7 @@ data CmmNode e x where
-- See Note [Unsafe foreign calls clobber caller-save registers]
--
-- Invariant: the arguments and the ForeignTarget must not
- -- mention any registers for which CodeGen.Platform.callerSaves
+ -- mention any registers for which GHC.Platform.callerSaves
-- is True. See Note [Register Parameter Passing].
CmmBranch :: ULabel -> CmmNode O C
@@ -199,7 +199,7 @@ sequence.
A foreign call is defined to clobber any GlobalRegs that are mapped to
caller-saves machine registers (according to the prevailing C ABI).
-StgCmmUtils.callerSaves tells you which GlobalRegs are caller-saves.
+GHC.StgToCmm.Utils.callerSaves tells you which GlobalRegs are caller-saves.
This is a design choice that makes it easier to generate code later.
We could instead choose to say that foreign calls do *not* clobber
@@ -221,7 +221,7 @@ convention, rdi, rsi, rdx and rcx (as well as r8 and r9) may be used for
argument passing. These are registers R3-R6, which our generated
code may also be using; as a result, it's necessary to save these
values before doing a foreign call. This is done during initial
-code generation in callerSaveVolatileRegs in StgCmmUtils.hs. However,
+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
diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y
index f563145250..319286ba5a 100644
--- a/compiler/cmm/CmmParse.y
+++ b/compiler/cmm/CmmParse.y
@@ -204,21 +204,21 @@ module CmmParse ( parseCmmFile ) where
import GhcPrelude
-import StgCmmExtCode
+import GHC.StgToCmm.ExtCode
import CmmCallConv
-import StgCmmProf
-import StgCmmHeap
-import StgCmmMonad hiding ( getCode, getCodeR, getCodeScoped, emitLabel, emit, emitStore
- , emitAssign, emitOutOfLine, withUpdFrameOff
- , getUpdFrameOff )
-import qualified StgCmmMonad as F
-import StgCmmUtils
-import StgCmmForeign
-import StgCmmExpr
-import StgCmmClosure
-import StgCmmLayout hiding (ArgRep(..))
-import StgCmmTicky
-import StgCmmBind ( emitBlackHoleCode, emitUpdateFrame )
+import GHC.StgToCmm.Prof
+import GHC.StgToCmm.Heap
+import GHC.StgToCmm.Monad hiding ( getCode, getCodeR, getCodeScoped, emitLabel, emit
+ , emitStore, emitAssign, emitOutOfLine, withUpdFrameOff
+ , getUpdFrameOff )
+import qualified GHC.StgToCmm.Monad as F
+import GHC.StgToCmm.Utils
+import GHC.StgToCmm.Foreign
+import GHC.StgToCmm.Expr
+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
diff --git a/compiler/cmm/CmmSink.hs b/compiler/cmm/CmmSink.hs
index 8a6b120377..7d945b0396 100644
--- a/compiler/cmm/CmmSink.hs
+++ b/compiler/cmm/CmmSink.hs
@@ -13,7 +13,7 @@ import Hoopl.Block
import Hoopl.Label
import Hoopl.Collections
import Hoopl.Graph
-import CodeGen.Platform
+import GHC.Platform.Regs
import GHC.Platform (isARM, platformArch)
import DynFlags
@@ -565,7 +565,7 @@ regsUsedIn ls e = wrapRecExpf f e False
-- clashing with C argument-passing registers, really the back-end
-- ought to be able to handle it properly, but currently neither PprC
-- nor the NCG can do it. See Note [Register parameter passing]
--- See also StgCmmForeign:load_args_into_temps.
+-- See also GHC.StgToCmm.Foreign.load_args_into_temps.
okToInline :: DynFlags -> CmmExpr -> CmmNode e x -> Bool
okToInline dflags expr node@(CmmUnsafeForeignCall{}) =
not (globalRegistersConflict dflags expr node)
diff --git a/compiler/cmm/CmmSwitch.hs b/compiler/cmm/CmmSwitch.hs
index ce779465e3..c2ce3b9e00 100644
--- a/compiler/cmm/CmmSwitch.hs
+++ b/compiler/cmm/CmmSwitch.hs
@@ -32,7 +32,7 @@ import qualified Data.Map as M
--
-- The overall plan is:
-- * The Stg → Cmm transformation creates a single `SwitchTargets` in
--- emitSwitch and emitCmmLitSwitch in StgCmmUtils.hs.
+-- emitSwitch and emitCmmLitSwitch in GHC.StgToCmm/Utils.hs.
-- At this stage, they are unsuitable for code generation.
-- * A dedicated Cmm transformation (CmmImplementSwitchPlans) replaces these
-- switch statements with code that is suitable for code generation, i.e.
diff --git a/compiler/cmm/CmmUtils.hs b/compiler/cmm/CmmUtils.hs
index 3381fbfcfd..1a28f94a0c 100644
--- a/compiler/cmm/CmmUtils.hs
+++ b/compiler/cmm/CmmUtils.hs
@@ -80,7 +80,7 @@ import CLabel
import Outputable
import DynFlags
import Unique
-import CodeGen.Platform
+import GHC.Platform.Regs
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
diff --git a/compiler/cmm/Debug.hs b/compiler/cmm/Debug.hs
index c874e81620..712dd4ba98 100644
--- a/compiler/cmm/Debug.hs
+++ b/compiler/cmm/Debug.hs
@@ -365,7 +365,7 @@ The remaining blocks are simple,
The flow of unwinding information through the compiler is a bit convoluted:
- * C-- begins life in StgCmm without any unwind information. This is because we
+ * C-- begins life in StgToCmm without any unwind information. This is because we
haven't actually done any register assignment or stack layout yet, so there
is no need for unwind information.
diff --git a/compiler/cmm/cmm-notes b/compiler/cmm/cmm-notes
index e2fb819222..600a62a617 100644
--- a/compiler/cmm/cmm-notes
+++ b/compiler/cmm/cmm-notes
@@ -90,106 +90,6 @@ Things to do:
(guided by the procpoint set)
----------------------------------------------------
- Modules in codeGen/
-----------------------------------------------------
-
-
-------- Shared ---------
-Bitmap.hs
-SMRep.lhs
-
-CmmParse.y
-CgExtCode.hs used in CmmParse.y
-
-------- New codegen ---------
-
-StgCmm.hs
-StgCmmBind.hs
-StgCmmClosure.hs (corresponds to old ClosureInfo)
-StgCmmCon.hs
-StgCmmEnv.hs
-StgCmmExpr.hs
-StgCmmForeign.hs
-StgCmmHeap.hs
-StgCmmHpc.hs
-StgCmmLayout.hs
-StgCmmMonad.hs
-StgCmmPrim.hs
-StgCmmProf.hs
-StgCmmTicky.hs
-StgCmmUtils.hs
-
-------- Old codegen (moribund) ---------
-CodeGen.lhs
-CgBindery.lhs
-CgCallConv.hs
-CgCase.lhs
-CgClosure.lhs
-CgCon.lhs
-CgExpr.lhs
-CgLetNoEscape.lhs
-CgForeignCall.hs
-CgHeapery.lhs
-CgHpc.hs
-CgInfoTbls.hs
-CgMonad.lhs
-CgParallel.hs
-CgPrimOp.hs
-CgProf.hs
-CgStackery.lhs
-CgTailCall.lhs
-CgTicky.hs
-CgUtils.hs
-ClosureInfo.lhs
-
-----------------------------------------------------
- Modules in cmm/
-----------------------------------------------------
-
--------- Moribund stuff ------------
-OldCmm.hs Definition of flowgraph of old representation
- Imports some data types from (new) Cmm
-OldCmmUtil.hs Utilites that operates mostly on on CmmStmt
-OldPprCmm.hs Pretty print for CmmStmt, GenBasicBlock and ListGraph
-CmmOpt.hs Hopefully-redundant optimiser
-
--------- Stuff to keep ------------
-CmmPipeline.hs Driver for new pipeline
-
-CmmLive.hs Liveness analysis, dead code elim
-CmmProcPoint.hs Identifying and splitting out proc-points
-
-CmmSpillReload.hs Save and restore across calls
-
-CmmCommonBlockElim.hs Common block elim
-CmmContFlowOpt.hs Other optimisations (branch-chain, merging)
-
-CmmBuildInfoTables.hs New info-table
-CmmStackLayout.hs and stack layout
-CmmCallConv.hs
-CmmInfo.hs Defn of InfoTables, and conversion to exact byte layout
-
----------- Cmm data types --------------
-Cmm.hs Cmm instantiations of dataflow graph framework
- CmmExpr.hs Type of Cmm expression
- CmmType.hs Type of Cmm types and their widths
- CmmMachOp.hs MachOp type and accompanying utilities
-
-PprCmm.hs Pretty printer for Cmm
- PprCmmExpr.hs Pretty printer for CmmExpr
-
-MkGraph.hs Interface for building Cmm for codeGen/Stg*.hs modules
-
-CmmUtils.hs
-CmmLint.hs
-
-PprC.hs Pretty print Cmm in C syntax
-
-CLabel.hs CLabel
-BlockId.hs BlockId, BlockEnv, BlockSet
-
-
-----------------------------------------------------
Proc-points
----------------------------------------------------
diff --git a/compiler/codeGen/CodeGen/Platform/NoRegs.hs b/compiler/codeGen/CodeGen/Platform/NoRegs.hs
deleted file mode 100644
index 4c074ee313..0000000000
--- a/compiler/codeGen/CodeGen/Platform/NoRegs.hs
+++ /dev/null
@@ -1,9 +0,0 @@
-{-# LANGUAGE CPP #-}
-
-module CodeGen.Platform.NoRegs where
-
-import GhcPrelude
-
-#define MACHREGS_NO_REGS 1
-#include "../../../../includes/CodeGen.Platform.hs"
-
diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in
index 479871c303..cf1d127fba 100644
--- a/compiler/ghc.cabal.in
+++ b/compiler/ghc.cabal.in
@@ -170,10 +170,10 @@ Library
cbits/genSym.c
hs-source-dirs:
+ .
backpack
basicTypes
cmm
- codeGen
coreSyn
deSugar
ghci
@@ -291,32 +291,32 @@ Library
PprCmmDecl
PprCmmExpr
Bitmap
- CodeGen.Platform
- CodeGen.Platform.ARM
- CodeGen.Platform.ARM64
- CodeGen.Platform.NoRegs
- CodeGen.Platform.PPC
- CodeGen.Platform.SPARC
- CodeGen.Platform.X86
- CodeGen.Platform.X86_64
- CgUtils
- StgCmm
- StgCmmBind
- StgCmmClosure
- StgCmmCon
- StgCmmEnv
- StgCmmExpr
- StgCmmForeign
- StgCmmHeap
- StgCmmHpc
- StgCmmArgRep
- StgCmmLayout
- StgCmmMonad
- StgCmmPrim
- StgCmmProf
- StgCmmTicky
- StgCmmUtils
- StgCmmExtCode
+ GHC.Platform.Regs
+ GHC.Platform.ARM
+ GHC.Platform.ARM64
+ GHC.Platform.NoRegs
+ GHC.Platform.PPC
+ GHC.Platform.SPARC
+ GHC.Platform.X86
+ GHC.Platform.X86_64
+ GHC.StgToCmm.CgUtils
+ GHC.StgToCmm
+ GHC.StgToCmm.Bind
+ GHC.StgToCmm.Closure
+ GHC.StgToCmm.Con
+ GHC.StgToCmm.Env
+ GHC.StgToCmm.Expr
+ GHC.StgToCmm.Foreign
+ GHC.StgToCmm.Heap
+ GHC.StgToCmm.Hpc
+ GHC.StgToCmm.ArgRep
+ GHC.StgToCmm.Layout
+ GHC.StgToCmm.Monad
+ GHC.StgToCmm.Prim
+ GHC.StgToCmm.Prof
+ GHC.StgToCmm.Ticky
+ GHC.StgToCmm.Utils
+ GHC.StgToCmm.ExtCode
SMRep
CoreArity
CoreFVs
diff --git a/compiler/ghci/ByteCodeAsm.hs b/compiler/ghci/ByteCodeAsm.hs
index 1b5c5b6cae..82de14346e 100644
--- a/compiler/ghci/ByteCodeAsm.hs
+++ b/compiler/ghci/ByteCodeAsm.hs
@@ -29,7 +29,7 @@ import NameSet
import Literal
import TyCon
import FastString
-import StgCmmLayout ( ArgRep(..) )
+import GHC.StgToCmm.Layout ( ArgRep(..) )
import SMRep
import DynFlags
import Outputable
diff --git a/compiler/ghci/ByteCodeGen.hs b/compiler/ghci/ByteCodeGen.hs
index ac7a5def0c..2865aaeaa6 100644
--- a/compiler/ghci/ByteCodeGen.hs
+++ b/compiler/ghci/ByteCodeGen.hs
@@ -48,8 +48,8 @@ import ErrUtils
import Unique
import FastString
import Panic
-import StgCmmClosure ( NonVoid(..), fromNonVoid, nonVoidIds )
-import StgCmmLayout
+import GHC.StgToCmm.Closure ( NonVoid(..), fromNonVoid, nonVoidIds )
+import GHC.StgToCmm.Layout
import SMRep hiding (WordOff, ByteOff, wordsToBytes)
import Bitmap
import OrdList
diff --git a/compiler/ghci/ByteCodeInstr.hs b/compiler/ghci/ByteCodeInstr.hs
index d405e1ade7..4347aa3867 100644
--- a/compiler/ghci/ByteCodeInstr.hs
+++ b/compiler/ghci/ByteCodeInstr.hs
@@ -17,7 +17,7 @@ import GhcPrelude
import ByteCodeTypes
import GHCi.RemoteTypes
import GHCi.FFI (C_ffi_cif)
-import StgCmmLayout ( ArgRep(..) )
+import GHC.StgToCmm.Layout ( ArgRep(..) )
import PprCore
import Outputable
import FastString
diff --git a/compiler/ghci/ByteCodeItbls.hs b/compiler/ghci/ByteCodeItbls.hs
index 7381c8f926..11d90bf5ed 100644
--- a/compiler/ghci/ByteCodeItbls.hs
+++ b/compiler/ghci/ByteCodeItbls.hs
@@ -20,8 +20,8 @@ import NameEnv
import DataCon ( DataCon, dataConRepArgTys, dataConIdentity )
import TyCon ( TyCon, tyConFamilySize, isDataTyCon, tyConDataCons )
import RepType
-import StgCmmLayout ( mkVirtConstrSizes )
-import StgCmmClosure ( tagForCon, NonVoid (..) )
+import GHC.StgToCmm.Layout ( mkVirtConstrSizes )
+import GHC.StgToCmm.Closure ( tagForCon, NonVoid (..) )
import Util
import Panic
diff --git a/compiler/ghci/RtClosureInspect.hs b/compiler/ghci/RtClosureInspect.hs
index c30d06ff3d..9fe18a57cf 100644
--- a/compiler/ghci/RtClosureInspect.hs
+++ b/compiler/ghci/RtClosureInspect.hs
@@ -856,7 +856,7 @@ extractSubTerms recurse clos = liftM thdOf3 . go 0 0
| otherwise = do
-- This is a bit involved since we allow packing multiple fields
-- within a single word. See also
- -- StgCmmLayout.mkVirtHeapOffsetsWithPadding
+ -- GHC.StgToCmm.Layout.mkVirtHeapOffsetsWithPadding
dflags <- getDynFlags
let word_size = wORD_SIZE dflags
big_endian = wORDS_BIGENDIAN dflags
@@ -864,7 +864,7 @@ extractSubTerms recurse clos = liftM thdOf3 . go 0 0
-- Align the start offset (eg, 2-byte value should be 2-byte
-- aligned). But not more than to a word. The offset calculation
-- should be the same with the offset calculation in
- -- StgCmmLayout.mkVirtHeapOffsetsWithPadding.
+ -- GHC.StgToCmm.Layout.mkVirtHeapOffsetsWithPadding.
!aligned_idx = roundUpTo arr_i (min word_size size_b)
!new_arr_i = aligned_idx + size_b
ws | size_b < word_size =
diff --git a/compiler/llvmGen/LlvmCodeGen.hs b/compiler/llvmGen/LlvmCodeGen.hs
index 399a81b183..cc86c4254e 100644
--- a/compiler/llvmGen/LlvmCodeGen.hs
+++ b/compiler/llvmGen/LlvmCodeGen.hs
@@ -18,7 +18,7 @@ import LlvmCodeGen.Regs
import LlvmMangler
import BlockId
-import CgUtils ( fixStgRegisters )
+import GHC.StgToCmm.CgUtils ( fixStgRegisters )
import Cmm
import CmmUtils
import Hoopl.Block
diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs
index e56be3ebb2..b132a1b023 100644
--- a/compiler/llvmGen/LlvmCodeGen/Base.hs
+++ b/compiler/llvmGen/LlvmCodeGen/Base.hs
@@ -45,7 +45,7 @@ import Llvm
import LlvmCodeGen.Regs
import CLabel
-import CodeGen.Platform ( activeStgRegs )
+import GHC.Platform.Regs ( activeStgRegs )
import DynFlags
import FastString
import Cmm hiding ( succ )
diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
index 86a59381b2..f86207e081 100644
--- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
+++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
@@ -14,7 +14,7 @@ import LlvmCodeGen.Base
import LlvmCodeGen.Regs
import BlockId
-import CodeGen.Platform ( activeStgRegs, callerSaves )
+import GHC.Platform.Regs ( activeStgRegs, callerSaves )
import CLabel
import Cmm
import PprCmm
diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs
index a9e443c08f..f2fc6e98d2 100644
--- a/compiler/main/HscMain.hs
+++ b/compiler/main/HscMain.hs
@@ -124,7 +124,7 @@ import SimplCore
import TidyPgm
import CorePrep
import CoreToStg ( coreToStg )
-import qualified StgCmm ( codeGen )
+import qualified GHC.StgToCmm as StgToCmm ( codeGen )
import StgSyn
import StgFVs ( annTopBindingsFreeVars )
import CostCentre
@@ -1412,7 +1412,7 @@ hscGenHardCode hsc_env cgguts mod_summary output_filename = do
withTiming (pure dflags)
(text "CodeGen"<+>brackets (ppr this_mod))
(const ()) $ do
- cmms <- {-# SCC "StgCmm" #-}
+ cmms <- {-# SCC "StgToCmm" #-}
doCodeGen hsc_env this_mod data_tycons
cost_centre_info
stg_binds hpc_info
@@ -1507,8 +1507,8 @@ doCodeGen hsc_env this_mod data_tycons
dumpIfSet_dyn dflags Opt_D_dump_stg_final
"STG for code gen:" (pprGenStgTopBindings stg_binds_w_fvs)
let cmm_stream :: Stream IO CmmGroup ()
- cmm_stream = {-# SCC "StgCmm" #-}
- StgCmm.codeGen dflags this_mod data_tycons
+ cmm_stream = {-# SCC "StgToCmm" #-}
+ StgToCmm.codeGen dflags this_mod data_tycons
cost_centre_info stg_binds_w_fvs hpc_info
-- codegen consumes a stream of CmmGroup, and produces a new
diff --git a/compiler/nativeGen/AsmCodeGen.hs b/compiler/nativeGen/AsmCodeGen.hs
index b735a3e412..0bbb07ffd8 100644
--- a/compiler/nativeGen/AsmCodeGen.hs
+++ b/compiler/nativeGen/AsmCodeGen.hs
@@ -72,7 +72,7 @@ import Dwarf
import Debug
import BlockId
-import CgUtils ( fixStgRegisters )
+import GHC.StgToCmm.CgUtils ( fixStgRegisters )
import Cmm
import CmmUtils
import Hoopl.Collections
diff --git a/compiler/nativeGen/Dwarf/Types.hs b/compiler/nativeGen/Dwarf/Types.hs
index a646f0bdfa..9066b3ebef 100644
--- a/compiler/nativeGen/Dwarf/Types.hs
+++ b/compiler/nativeGen/Dwarf/Types.hs
@@ -46,7 +46,7 @@ import qualified Data.Map as Map
import Data.Word
import Data.Char
-import CodeGen.Platform
+import GHC.Platform.Regs
-- | Individual dwarf records. Each one will be encoded as an entry in
-- the @.debug_info@ section.
diff --git a/compiler/nativeGen/PPC/CodeGen.hs b/compiler/nativeGen/PPC/CodeGen.hs
index a49526c93a..5ae9ce76ec 100644
--- a/compiler/nativeGen/PPC/CodeGen.hs
+++ b/compiler/nativeGen/PPC/CodeGen.hs
@@ -27,7 +27,7 @@ where
-- NCG stuff:
import GhcPrelude
-import CodeGen.Platform
+import GHC.Platform.Regs
import PPC.Instr
import PPC.Cond
import PPC.Regs
diff --git a/compiler/nativeGen/PPC/Instr.hs b/compiler/nativeGen/PPC/Instr.hs
index ee8edd86fd..22dc4ff6e1 100644
--- a/compiler/nativeGen/PPC/Instr.hs
+++ b/compiler/nativeGen/PPC/Instr.hs
@@ -33,7 +33,7 @@ import TargetReg
import RegClass
import Reg
-import CodeGen.Platform
+import GHC.Platform.Regs
import BlockId
import Hoopl.Collections
import Hoopl.Label
diff --git a/compiler/nativeGen/PPC/Regs.hs b/compiler/nativeGen/PPC/Regs.hs
index 5b7ac208b6..02940e593a 100644
--- a/compiler/nativeGen/PPC/Regs.hs
+++ b/compiler/nativeGen/PPC/Regs.hs
@@ -60,7 +60,7 @@ import Cmm
import CLabel ( CLabel )
import Unique
-import CodeGen.Platform
+import GHC.Platform.Regs
import DynFlags
import Outputable
import GHC.Platform
diff --git a/compiler/nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs b/compiler/nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs
index 5528a38727..5df329359d 100644
--- a/compiler/nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs
+++ b/compiler/nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs
@@ -9,7 +9,7 @@ import SPARC.Regs
import RegClass
import Reg
-import CodeGen.Platform
+import GHC.Platform.Regs
import Outputable
import GHC.Platform
diff --git a/compiler/nativeGen/SPARC/CodeGen/Base.hs b/compiler/nativeGen/SPARC/CodeGen/Base.hs
index 97c54a9364..8a2f2f5a08 100644
--- a/compiler/nativeGen/SPARC/CodeGen/Base.hs
+++ b/compiler/nativeGen/SPARC/CodeGen/Base.hs
@@ -22,7 +22,7 @@ import SPARC.Regs
import Format
import Reg
-import CodeGen.Platform
+import GHC.Platform.Regs
import DynFlags
import Cmm
import PprCmmExpr () -- For Outputable instances
diff --git a/compiler/nativeGen/SPARC/Instr.hs b/compiler/nativeGen/SPARC/Instr.hs
index f57b6fafb5..77a93af1fc 100644
--- a/compiler/nativeGen/SPARC/Instr.hs
+++ b/compiler/nativeGen/SPARC/Instr.hs
@@ -40,7 +40,7 @@ import Reg
import Format
import CLabel
-import CodeGen.Platform
+import GHC.Platform.Regs
import BlockId
import DynFlags
import Cmm
diff --git a/compiler/nativeGen/SPARC/Regs.hs b/compiler/nativeGen/SPARC/Regs.hs
index 0d7edc346a..8f470ad79d 100644
--- a/compiler/nativeGen/SPARC/Regs.hs
+++ b/compiler/nativeGen/SPARC/Regs.hs
@@ -34,7 +34,7 @@ where
import GhcPrelude
-import CodeGen.Platform.SPARC
+import GHC.Platform.SPARC
import Reg
import RegClass
import Format
diff --git a/compiler/nativeGen/X86/CodeGen.hs b/compiler/nativeGen/X86/CodeGen.hs
index 4aeb4eb635..a5b64760a2 100644
--- a/compiler/nativeGen/X86/CodeGen.hs
+++ b/compiler/nativeGen/X86/CodeGen.hs
@@ -38,7 +38,7 @@ import X86.Cond
import X86.Regs
import X86.RegInfo
-import CodeGen.Platform
+import GHC.Platform.Regs
import CPrim
import Debug ( DebugBlock(..), UnwindPoint(..), UnwindTable
, UnwindExpr(UwReg), toUnwindExpr )
diff --git a/compiler/nativeGen/X86/Instr.hs b/compiler/nativeGen/X86/Instr.hs
index 6e5d656beb..776e2d9389 100644
--- a/compiler/nativeGen/X86/Instr.hs
+++ b/compiler/nativeGen/X86/Instr.hs
@@ -30,7 +30,7 @@ import TargetReg
import BlockId
import Hoopl.Collections
import Hoopl.Label
-import CodeGen.Platform
+import GHC.Platform.Regs
import Cmm
import FastString
import Outputable
diff --git a/compiler/nativeGen/X86/Regs.hs b/compiler/nativeGen/X86/Regs.hs
index 2d9fd88c8e..6d21545563 100644
--- a/compiler/nativeGen/X86/Regs.hs
+++ b/compiler/nativeGen/X86/Regs.hs
@@ -52,7 +52,7 @@ where
import GhcPrelude
-import CodeGen.Platform
+import GHC.Platform.Regs
import Reg
import RegClass
diff --git a/compiler/prelude/PrelRules.hs b/compiler/prelude/PrelRules.hs
index 83313a3ca9..d44c940d35 100644
--- a/compiler/prelude/PrelRules.hs
+++ b/compiler/prelude/PrelRules.hs
@@ -1079,7 +1079,7 @@ is:
regardless of the evaluated-ness of their argument.
See CoreUtils Note [exprOkForSpeculation and SeqOp/DataToTagOp]
-* There is a special case for DataToTagOp in StgCmmExpr.cgExpr,
+* There is a special case for DataToTagOp in GHC.StgToCmm.Expr.cgExpr,
that evaluates its argument and then extracts the tag from
the returned value.
@@ -1146,7 +1146,7 @@ Implementing seq#. The compiler has magic for SeqOp in
- PrelRules.seqRule: eliminate (seq# <whnf> s)
-- StgCmmExpr.cgExpr, and cgCase: special case for seq#
+- GHC.StgToCmm.Expr.cgExpr, and cgCase: special case for seq#
- CoreUtils.exprOkForSpeculation;
see Note [exprOkForSpeculation and SeqOp/DataToTagOp] in CoreUtils
diff --git a/compiler/simplStg/StgLiftLams/Analysis.hs b/compiler/simplStg/StgLiftLams/Analysis.hs
index c2d4dfdb7c..104c2f8ef3 100644
--- a/compiler/simplStg/StgLiftLams/Analysis.hs
+++ b/compiler/simplStg/StgLiftLams/Analysis.hs
@@ -28,9 +28,9 @@ import DynFlags
import Id
import SMRep ( WordOff )
import StgSyn
-import qualified StgCmmArgRep
-import qualified StgCmmClosure
-import qualified StgCmmLayout
+import qualified GHC.StgToCmm.ArgRep as StgToCmm.ArgRep
+import qualified GHC.StgToCmm.Closure as StgToCmm.Closure
+import qualified GHC.StgToCmm.Layout as StgToCmm.Layout
import Outputable
import Util
import VarSet
@@ -447,7 +447,7 @@ goodToLift dflags top_lvl rec_flag expander pairs scope = decide
-- to lift it
n_args
= length
- . StgCmmClosure.nonVoidIds -- void parameters don't appear in Cmm
+ . StgToCmm.Closure.nonVoidIds -- void parameters don't appear in Cmm
. (dVarSetElems abs_ids ++)
. rhsLambdaBndrs
max_n_args
@@ -490,19 +490,19 @@ closureSize dflags ids = words + sTD_HDR_SIZE dflags
where
(words, _, _)
-- Functions have a StdHeader (as opposed to ThunkHeader).
- = StgCmmLayout.mkVirtHeapOffsets dflags StgCmmLayout.StdHeader
- . StgCmmClosure.addIdReps
- . StgCmmClosure.nonVoidIds
+ = StgToCmm.Layout.mkVirtHeapOffsets dflags StgToCmm.Layout.StdHeader
+ . StgToCmm.Closure.addIdReps
+ . StgToCmm.Closure.nonVoidIds
$ ids
-- | The number of words a single 'Id' adds to a closure's size.
-- Note that this can't handle unboxed tuples (which may still be present in
-- let-no-escapes, even after Unarise), in which case
--- @'StgCmmClosure.idPrimRep'@ will crash.
+-- @'GHC.StgToCmm.Closure.idPrimRep'@ will crash.
idClosureFootprint:: DynFlags -> Id -> WordOff
idClosureFootprint dflags
- = StgCmmArgRep.argRepSizeW dflags
- . StgCmmArgRep.idArgRep
+ = StgToCmm.ArgRep.argRepSizeW dflags
+ . StgToCmm.ArgRep.idArgRep
-- | @closureGrowth expander sizer f fvs@ computes the closure growth in words
-- as a result of lifting @f@ to top-level. If there was any growing closure
diff --git a/compiler/simplStg/UnariseStg.hs b/compiler/simplStg/UnariseStg.hs
index 57e9f3351a..5c1d2b5c5d 100644
--- a/compiler/simplStg/UnariseStg.hs
+++ b/compiler/simplStg/UnariseStg.hs
@@ -185,7 +185,7 @@ STG programs after unarisation have these invariants:
* DataCon applications (StgRhsCon and StgConApp) don't have void arguments.
This means that it's safe to wrap `StgArg`s of DataCon applications with
- `StgCmmEnv.NonVoid`, for example.
+ `GHC.StgToCmm.Env.NonVoid`, for example.
* Alt binders (binders in patterns) are always non-void.
diff --git a/compiler/stgSyn/StgSyn.hs b/compiler/stgSyn/StgSyn.hs
index 0507635b94..a00e8ad2ba 100644
--- a/compiler/stgSyn/StgSyn.hs
+++ b/compiler/stgSyn/StgSyn.hs
@@ -676,7 +676,7 @@ data StgOp
| StgFCallOp ForeignCall Type
-- The Type, which is obtained from the foreign import declaration
-- itself, is needed by the stg-to-cmm pass to determine the offset to
- -- apply to unlifted boxed arguments in StgCmmForeign. See Note
+ -- apply to unlifted boxed arguments in GHC.StgToCmm.Foreign. See Note
-- [Unlifted boxed arguments to foreign calls]
{-
diff --git a/docs/stg-spec/stg-spec.mng b/docs/stg-spec/stg-spec.mng
index 325410e218..7e87c151d9 100644
--- a/docs/stg-spec/stg-spec.mng
+++ b/docs/stg-spec/stg-spec.mng
@@ -171,7 +171,7 @@ and over-saturated function application.
The implementations of \textsc{App} rules are spread across two
different calling conventions for functions: slow calls and
direct calls. Direct calls handle saturated and over-applied
-cases (\coderef{codeGen/StgCmmLayout.hs}{slowArgs}), while slow
+cases (\coderef{GHC/StgToCmm/Layout.hs}{slowArgs}), while slow
calls handle all cases (\textit{utils/genapply/GenApply.hs});
in particular, these cases ensure that the current cost-center
reverts to the one originally at the call site.
diff --git a/includes/rts/prof/CCS.h b/includes/rts/prof/CCS.h
index b296a32b8a..7685f03003 100644
--- a/includes/rts/prof/CCS.h
+++ b/includes/rts/prof/CCS.h
@@ -22,7 +22,7 @@
* putting the 8-byte fields on an 8-byte boundary. Padding can
* vary between C compilers, and we don't take into account any
* possible padding when generating CCS and CC decls in the code
- * generator (compiler/codeGen/StgCmmProf.hs).
+ * generator (GHC.StgToCmm.Prof).
*/
typedef struct CostCentre_ {
diff --git a/includes/rts/storage/FunTypes.h b/includes/rts/storage/FunTypes.h
index 27858fb82b..88fcc5878c 100644
--- a/includes/rts/storage/FunTypes.h
+++ b/includes/rts/storage/FunTypes.h
@@ -24,7 +24,7 @@
*
* NOTE: other places to change if you change this table:
* - utils/genapply/Main.hs: stackApplyTypes
- * - compiler/codeGen/StgCmmLayout.hs: stdPattern
+ * - GHC.StgToCmm.Layout: stdPattern
*/
#define ARG_NONE 3
#define ARG_N 4
diff --git a/includes/stg/MiscClosures.h b/includes/stg/MiscClosures.h
index 4cec0b961c..217b1bc89d 100644
--- a/includes/stg/MiscClosures.h
+++ b/includes/stg/MiscClosures.h
@@ -243,7 +243,7 @@ RTS_THUNK(stg_ap_6_upd);
RTS_THUNK(stg_ap_7_upd);
/* standard application routines (see also utils/genapply,
- * and compiler/codeGen/StgCmmArgRep.hs).
+ * and GHC.StgToCmm.ArgRep).
*/
RTS_RET(stg_ap_v);
RTS_RET(stg_ap_f);
@@ -528,13 +528,13 @@ extern StgWord CCS_OVERHEAD[];
extern StgWord CCS_SYSTEM[];
// Calls to these rts functions are generated directly
-// by codegen (see compiler/codeGen/StgCmmProf.hs)
+// by codegen (see GHC.StgToCmm.Prof)
// and don't require (don't emit) forward declarations.
//
// In unregisterised mode (when building via .hc files)
// the calls are ordinary C calls. Functions must be in
// scope and must match prototype assumed by
-// 'compiler/codeGen/StgCmmProf.hs'
+// 'GHC.StgToCmm.Prof'
// as opposed to real prototype declared in
// 'includes/rts/prof/CCS.h'
void enterFunCCS (void *reg, void *ccsfn);
diff --git a/includes/stg/SMP.h b/includes/stg/SMP.h
index 5487a9a4d6..4be11d1f64 100644
--- a/includes/stg/SMP.h
+++ b/includes/stg/SMP.h
@@ -166,7 +166,7 @@ EXTERN_INLINE void load_load_barrier(void);
*
* - Eager blackholing a THUNK:
* This is protected by an explicit write barrier in the eager blackholing
- * code produced by the codegen. See StgCmmBind.emitBlackHoleCode.
+ * code produced by the codegen. See GHC.StgToCmm.Bind.emitBlackHoleCode.
*
* - Lazy blackholing a THUNK:
* This is is protected by an explicit write barrier in the thread suspension
@@ -189,8 +189,8 @@ EXTERN_INLINE void load_load_barrier(void);
*
* - Write to an Array#, ArrayArray#, or SmallArray#:
* This case is protected by an explicit write barrier in the code produced
- * for this primop by the codegen. See StgCmmPrim.doWritePtrArrayOp and
- * StgCmmPrim.doWriteSmallPtrArrayOp. Relevant issue: #12469.
+ * for this primop by the codegen. See GHC.StgToCmm.Prim.doWritePtrArrayOp and
+ * GHC.StgToCmm.Prim.doWriteSmallPtrArrayOp. Relevant issue: #12469.
*
* - Write to MutVar# via writeMutVar#:
* This case is protected by an explicit write barrier in the code produced
diff --git a/rts/PrimOps.cmm b/rts/PrimOps.cmm
index d9a28d7396..777dc93637 100644
--- a/rts/PrimOps.cmm
+++ b/rts/PrimOps.cmm
@@ -2509,7 +2509,7 @@ stg_setThreadAllocationCounterzh ( I64 counter )
// Allocation in the current block will be subtracted by
// getThreadAllocationCounter#, so we have to offset any existing
// allocation here. See also openNursery/closeNursery in
- // compiler/codeGen/StgCmmForeign.hs.
+ // GHC.StgToCmm.Foreign.
W_ offset;
offset = Hp - bdescr_start(CurrentNursery);
StgTSO_alloc_limit(CurrentTSO) = counter + TO_I64(offset);
diff --git a/testsuite/tests/codeGen/should_run/T13825-unit.hs b/testsuite/tests/codeGen/should_run/T13825-unit.hs
index 40088aa734..34a13acb50 100644
--- a/testsuite/tests/codeGen/should_run/T13825-unit.hs
+++ b/testsuite/tests/codeGen/should_run/T13825-unit.hs
@@ -3,8 +3,8 @@ module Main where
import DynFlags
import RepType
import SMRep
-import StgCmmLayout
-import StgCmmClosure
+import GHC.StgToCmm.Layout
+import GHC.StgToCmm.Closure
import GHC
import GhcMonad
import System.Environment
diff --git a/testsuite/tests/regalloc/regalloc_unit_tests.hs b/testsuite/tests/regalloc/regalloc_unit_tests.hs
index 18e0f3b5f4..5c6d9da624 100644
--- a/testsuite/tests/regalloc/regalloc_unit_tests.hs
+++ b/testsuite/tests/regalloc/regalloc_unit_tests.hs
@@ -24,7 +24,7 @@ import qualified RegAlloc.Graph.Stats as Color
import qualified RegAlloc.Linear.Base as Linear
import qualified X86.Instr
import HscMain
-import CgUtils
+import GHC.StgToCmm.CgUtils
import AsmCodeGen
import CmmBuildInfoTables
import CmmPipeline
diff --git a/utils/genapply/Main.hs b/utils/genapply/Main.hs
index 270bc61615..4a9d1e1526 100644
--- a/utils/genapply/Main.hs
+++ b/utils/genapply/Main.hs
@@ -1000,7 +1000,7 @@ applyTypes = [
--
-- NOTE: other places to change if you change stackApplyTypes:
-- - includes/rts/storage/FunTypes.h
--- - compiler/codeGen/StgCmmLayout.hs: stdPattern
+-- - GHC.StgToCmm.Layout: stdPattern
stackApplyTypes = [
[],
[N],