diff --git a/aclocal.m4 b/aclocal.m4 index 4a037a46fdf7430afcae0c4430f221e3c128d016..3dc30eb7d9ea3c4b5cc348c5437e74d90516bd67 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 similarity index 94% rename from compiler/cmm/Cmm.hs rename to compiler/GHC/Cmm.hs index e08b22fa9bd607b85511e868393ff846f6ffb7aa..5efecdc53486532e54924161289b374cf5e013e3 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 similarity index 92% rename from compiler/cmm/BlockId.hs rename to compiler/GHC/Cmm/BlockId.hs index 4f4e0e8c53280c2eccb597814d250fc87412d689..f7f369551bda9254e5b220292fdc28d60f942d7f 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 0000000000000000000000000000000000000000..76fd6180a9465c8e434c7fced7227d18bd7a455e --- /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 similarity index 99% rename from compiler/cmm/CLabel.hs rename to compiler/GHC/Cmm/CLabel.hs index fb2f06716da2a380556891d8278737cb3f658dcb..e84278bf65493a350bef34b9c9bd742cf610d782 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 similarity index 98% rename from compiler/cmm/CmmCallConv.hs rename to compiler/GHC/Cmm/CallConv.hs index df1eaad0057d0dd6b01ada57e3e1e58a736eabd9..9200daec570f49e8716b8023f6c0d33fb213d08f 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 similarity index 97% rename from compiler/cmm/CmmCommonBlockElim.hs rename to compiler/GHC/Cmm/CommonBlockElim.hs index cbf7d83d36b950bb8aaa6b235f946fed1cdc7e47..86ea0e94e28c3b7ddc54c85787b4635ad1f6a635 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 similarity index 98% rename from compiler/cmm/CmmContFlowOpt.hs rename to compiler/GHC/Cmm/ContFlowOpt.hs index 606da02969a8d33e515876fb42b80efc724bb75f..7765972d02273cfc7c058aee1a4cfed01bd04e71 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 similarity index 98% rename from compiler/cmm/Hoopl/Dataflow.hs rename to compiler/GHC/Cmm/Dataflow.hs index 9762a84e20e85e99f411a8daca53da9579ca6a4e..fcabb1df0fbb9990e7cd17c0bfae43cbe308ba05 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 similarity index 99% rename from compiler/cmm/Hoopl/Block.hs rename to compiler/GHC/Cmm/Dataflow/Block.hs index 07aafe8ae95617bfb19465b7629e6776c7a881ad..d2e52a89049c2850b48c466dd1c5f7b99b6d8dfd 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 similarity index 99% rename from compiler/cmm/Hoopl/Collections.hs rename to compiler/GHC/Cmm/Dataflow/Collections.hs index 4c5516be79883a18abf4d6a52c0ad74a67181818..f131f17cc188d66c658a7c140e7ec046df862567 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 similarity index 98% rename from compiler/cmm/Hoopl/Graph.hs rename to compiler/GHC/Cmm/Dataflow/Graph.hs index 992becb417f6d378e30557f2e61c1d31b8eb10d9..3f361de0fbd6f298e30b0f0b64d4af5d7f5d792c 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 similarity index 98% rename from compiler/cmm/Hoopl/Label.hs rename to compiler/GHC/Cmm/Dataflow/Label.hs index 2e75d97244bdb1f7e2a7a71802d0f6050b4a8a16..c571cedb480b758325f659a7b2a533cb19a49eb8 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 similarity index 98% rename from compiler/cmm/Debug.hs rename to compiler/GHC/Cmm/DebugBlock.hs index 712dd4ba98ce6e980c02a05ba070abf0ea9ea911..70fc08ee94d7d42315dc1ec9694eea46529ff405 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 similarity index 98% rename from compiler/cmm/CmmExpr.hs rename to compiler/GHC/Cmm/Expr.hs index 860ee1a7f5b3ccba9ec5c5e49bb144b65dab919e..3b4f0156a08081200984ecdaf33189f79ce0c74e 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 similarity index 98% rename from compiler/cmm/MkGraph.hs rename to compiler/GHC/Cmm/Graph.hs index c6e62435a27127d67b99c6ca3193921b2dcec64b..8d19e7fdb9cce2f712a28ec24cfb304412d51361 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 similarity index 99% rename from compiler/cmm/CmmInfo.hs rename to compiler/GHC/Cmm/Info.hs index 3ef3d5001e06531243c1d67a8e24914231093e94..a10db2b292954bfe0addd049f4f60c11dc4eba3c 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 similarity index 99% rename from compiler/cmm/CmmBuildInfoTables.hs rename to compiler/GHC/Cmm/Info/Build.hs index 81c86fdad520ca06728be04efab41964b51aa9f3..1ba79befcdd4abfade650c3261f06ab62fcdf82f 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 similarity index 99% rename from compiler/cmm/CmmLayoutStack.hs rename to compiler/GHC/Cmm/LayoutStack.hs index e26f2878c0b1362be3308d1fc1b3394a923697cd..f6dda7728c4d6aee03886be1b92471c932f05f13 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 similarity index 99% rename from compiler/cmm/CmmLex.x rename to compiler/GHC/Cmm/Lexer.x index 468ea00a93f3ba925217f11a80dc2ddd7fc4c5e5..d8f15b916ce7c41656b8f31f98fa2026fa209e4a 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 similarity index 95% rename from compiler/cmm/CmmLint.hs rename to compiler/GHC/Cmm/Lint.hs index 3ad65bd53632fbb980b654fd1b89d8986a895efa..d70fed3b9e5c6969ffa003797a1579b46d59fab5 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 similarity index 92% rename from compiler/cmm/CmmLive.hs rename to compiler/GHC/Cmm/Liveness.hs index ca474ef61c182d5950087e5d4342b360a03231de..2b598f52e574d479b5d3adedbdf9851c49c7b3c9 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 similarity index 99% rename from compiler/cmm/CmmMachOp.hs rename to compiler/GHC/Cmm/MachOp.hs index 418ebec13f39f4927b2227685c5fcda69cf51d2e..234001545c3992e30865fa9bf077c12cf7ee2f1c 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 similarity index 98% rename from compiler/cmm/CmmMonad.hs rename to compiler/GHC/Cmm/Monad.hs index a04c4ad49bffd8319ac62fb3995f1bb80796f7e9..6b8d00a118993a81cfd3225354115be73ed1d3a2 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 similarity index 98% rename from compiler/cmm/CmmNode.hs rename to compiler/GHC/Cmm/Node.hs index f9bad961e664f04fa929d4750cc8e61d70b7a018..bb746479105732a3dfdaabbae96e017ceee166a5 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 similarity index 99% rename from compiler/cmm/CmmOpt.hs rename to compiler/GHC/Cmm/Opt.hs index 5b542a390e761140a6994d2ba9479770ce65e257..1db37ae58cd22ca70d782a47daf7d2fd43db07f3 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 similarity index 99% rename from compiler/cmm/CmmParse.y rename to compiler/GHC/Cmm/Parser.y index e5683781976bbd78a8c36ad651a522a52c1a1fb2..d7235d0167f3d5d3a756e166c91d7691255e6c20 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 similarity index 97% rename from compiler/cmm/CmmPipeline.hs rename to compiler/GHC/Cmm/Pipeline.hs index e7689a6bfe89155d0f392e606090fbcdf5f60ca5..6db9e23ee1cf7e1be0b0aaa78893d506c79834e7 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 similarity index 97% rename from compiler/cmm/PprCmm.hs rename to compiler/GHC/Cmm/Ppr.hs index 397a6660229f5de22a0b6aed1a1a62d8b113dc8b..891cbd9c6d4b05609ca37021f18bab6b56ceca14 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 similarity index 98% rename from compiler/cmm/PprCmmDecl.hs rename to compiler/GHC/Cmm/Ppr/Decl.hs index e54abdc8b6961f2c3449426219323545963a68cb..2544e6a0d3cd153260089111f9ab835975272b80 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 similarity index 98% rename from compiler/cmm/PprCmmExpr.hs rename to compiler/GHC/Cmm/Ppr/Expr.hs index 7bf73f1ca69a53ce5d17f44428e39064598791b9..53a335e561cf3b5865f4d22ee71425b6e092303c 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 similarity index 97% rename from compiler/cmm/CmmProcPoint.hs rename to compiler/GHC/Cmm/ProcPoint.hs index 746a175cfe3fa068098ede0c0612db836af2a353..00a7a73d89656b3eeb0e3326dfe3ae72cfa361b4 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 similarity index 99% rename from compiler/cmm/CmmSink.hs rename to compiler/GHC/Cmm/Sink.hs index 7d945b0396ce702468151b5c2ae27ed4e9338c15..8e231df3000a9319087ea8e9f163ae8f5fb95e4d 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 similarity index 93% rename from compiler/cmm/CmmSwitch.hs rename to compiler/GHC/Cmm/Switch.hs index 26bf5c4ce90c62061af92029b0d88d115527dd90..e89fadfd2ed63b985b06128aa0f7d40247398688 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 similarity index 92% rename from compiler/cmm/CmmImplementSwitchPlans.hs rename to compiler/GHC/Cmm/Switch/Implement.hs index 83c29cf6b51b93487e9d5d117478bad386a1ea96..dfac116764f4307036cd2ed3a2a5fb226d59d3b3 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 similarity index 99% rename from compiler/cmm/CmmType.hs rename to compiler/GHC/Cmm/Type.hs index f8ac71ac897c97bd7b63c8a3ff63bf8a983e2e52..867a260078fd84cefc1504337d8d2a310484d74a 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 similarity index 98% rename from compiler/cmm/CmmUtils.hs rename to compiler/GHC/Cmm/Utils.hs index 8920d2d6b930bd05bff61dc13d33cfce0c95f5b0..d879c7b82fefc835a3e49df74bc54bab539a8867 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 similarity index 98% rename from compiler/cmm/cmm-notes rename to compiler/GHC/Cmm/cmm-notes index 699f218257b80806d3afb376c4e26c7ead464c91..d664a195b713edbb561bc5322cadd0eeddfc012e 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 similarity index 99% rename from compiler/cmm/PprC.hs rename to compiler/GHC/CmmToC.hs index d94bc01e03f43a71c94e427d9a1df34bcaf71606..a413820e306b4d1b83216083025c587159e4d723 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 similarity index 97% rename from compiler/cmm/Bitmap.hs rename to compiler/GHC/Data/Bitmap.hs index 42acc5f3cd85b4e5e09955c669a8e12b700dad9c..a8eba5e2e82846aa0148ea7bf0d5d6ae209c3b18 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 c304d4f5ad1ee4b77240ea4ae360ef9dd3a32114..51f7658db21ea4df9532bb301003ed3c40337e02 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 similarity index 99% rename from compiler/cmm/SMRep.hs rename to compiler/GHC/Runtime/Layout.hs index fe4ed58bfeb788fc322543eedcb3214f73a88ad8..8f245479c1eb1278da48bc4e954c179e1d6293b0 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 02d439cef7134304a0dbacfe81d073866891d4f1..ccbad372100e9f4a3afefd935f17f74d5e28f835 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 10a9dc2c6adadcb072015c28e5629a1d7cb93dad..f489ce645639ba298fd8788a86ee94e6e4eb56fb 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 cc2fe8306aaa9b486d8d853fb12a3f3c226d55fd..347d908b4498524ec16adcc12c507eccc12e74a6 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 b1cb34ace7783612dabae855ef23596d73d3cf60..a78ab5cb41d887808f78932101b669db73f29642 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 f3dccd97451cca8a3699b264d62b33f09f4b33a0..58c46f8fa2ad6a9f241c3b419a16f8b4952b7e42 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 df8cb046c4e88420cc8eb152995f50308521c0d1..724ca6000a009f615c0d343dff705f48a126f230 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 1e929663dfb992e2e8ead7f92a0ec39e768399c7..2bbeabace623e4cf002d5ccc13343a7f2a7efa60 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 45b09a3d26097b8570eee6dc1409ae41b524eee1..b2c1371840a2b8ca154b8e21255fbf3907b533ff 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 3836aa3d2a207cb3e164a8f195b96ef2477784c2..0c2d9b8ae57ca39c163627f22fb7ee17f156c9bf 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 4a5225eec6e176e904c7642bb856d24f88da6bf3..2679ce49920b3b9f9d62efd37efc469dc0439c2e 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 3ef0872c2e899902d5ca170e1d2ec053b14dcbb8..62a948d13cdd6aa90bc731ce084a99e1d3ff49f0 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 d36cad5788c74b6b25e4ad0135c8ce1799142ae0..492a4460f886c695922ca2b98055c84ff1ef3e9c 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 e33d39245c171cf8e6ac2a4979c31acb80d178c7..a3f41122069d6027cfb768f93abdda09f6d6eb56 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 6d7825eb935a200298348dbdbf54e6089ac42d7d..e78221de3aa615e717cedf11b8977a196b97a349 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 716cbdab781e87e404251936cf3fcb8f23742ceb..4f7d2e122088154fb38947811a87d4979a6aeef3 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 e469e15a5d8bb164ad1f887d951c15b35b36dce1..06264099dfa2732454927769fe81db36b4b663d3 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 4743b796225c251ee39050376195c4d731bec094..cf5ce5acfb81b24ca02f9515a2fcacd1d2511ef2 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 9eeb134cc965f4be7f0078db128ffc9b78920aa4..6e2e2d3a6bd20b093a50405a8f3fb124f298f8aa 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 34fb93468c5b31ae2f803e3c3a68be3434056bcd..7a784ea85ca5685d54cda3cff0f14b67795d19b7 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 4a646aa70a4d427d01e2b10034171b5944752fe3..f14f22d6253789a65a565d93ecbbeeda1234c05f 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 3ad414118457fa05b02647f7909672e0bac74660..0000000000000000000000000000000000000000 --- 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 75eeb075700328ed4fccc2348123f480bc95869f..d94f640f84ee588daa75999b74ef624a23e35bd0 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 0a3755e94beae15cc410fd2c5426bffe6e7e3f60..cdf58e709ea4e0f176a989a3827001b30394df8a 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 640f325c033981c89acb41cf104e1a560c635347..ddcf2aeacbb26ac89bf21b203855d3aecb604d45 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 82de14346e92fe4fad22e06ce8c8cc2d48be5270..801cdc7068b2faa39dd27aacd14c9dc6f1b98b66 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 2e24bf540cff9860e73bd2e541a9513b41d740b4..186d094bff7404923ee816b109d58b449bce3df4 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 b0db198037498c08fb66a54007588bdcd8f0260b..9cdd297dbdc0f0cadc6042e57eea568e6d084107 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 96df8b547c163e350663f3d5c7033855b572b0a4..a523ae07bf48c1d035ee10c41b383f10b1717e8e 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 0fc7e76e581eca58c189b4558f73e36442c63492..8bff8fd6e500d1bb8154031d728988d5461651f4 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 ce9f22052fdc02440eb25c9743727b621d9c00fd..165f733af44d6c1c491b2bf8b09cbeea970fe9d8 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 bfaf7706d1424e7983e1ceff0ee8b856de69d545..f9b10679ef1a9c6ce063c7395153a741d1fb3296 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 4c07f8ee8f67f96d3c4a51d816f45fbc1869d85e..46fb1afbcd61f21a7479745695b03425aa2b3bc9 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 3f29133e59d0e07d2fc98d68c17525e579307199..5fcc72f25a19660ff593a3cc591fa59315330493 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 8cdf3c686994f07394beff5e99743523a9dc0c0d..4b1a15674ef2903178bbf927a78abf9776e09021 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 2b9770c78ec2a2e2f78d02b8b4813461775c9ef2..6656a4f4d8ea40d9af8b17d34621aa880d7b9795 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 d5ced7d5a0b1c3b60237ecfc1d0a3a6b523eac61..8caebfc5562ae85a0d4f05e50046f3dd7abe17c8 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 ffb9b3ced938c742ea4507761be0559b26a0d3f0..1c27542270d2e1038b6603e2e8ba3bf1fe695cf7 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 4f67ba0190e4c771718133b7d34c0b5066e47c8b..dfc54799d7bdfb4809784fc2e8dfd84fd12debc6 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 556c943dc28794e57ccc8b4152341b27fdc8546a..021fbae19542aa4793a3403c4f1640c15baef9ea 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 5e81316ab3e267b5c57ee3ab16bbcc4017a5901c..3f74065e4e9008e3ed87eaeb3404c4356255644e 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 4dc5f9ccb39b0791eea7b650aff4ab804f00058d..90573221f85e95469247641a04479bf074e45de9 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 17e5cda8457fd8e60788bc4da330788be59e7204..344e62d53c2e94906a286c4f77955f1278a6d083 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 33f1c5b2f7ee482103ec0fd6b11948fa365cb91a..a64df287f54b7ba68a1eb07b157315e0f9912925 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 a6ba596f350f463b01051920a0ebbd14d5f25fae..df578e26713c1569492214a582d19df3552fd59a 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 745d1e7b655097dc0cebd73f322a4d4c053fa715..d7b6f6b86831e440c3d635291a9ac5b4f5393fc3 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 4f18a45c16b0b5788ffdf80be7bb89886d44a672..150bd8adbacc8923b39b4e2e378c2536874d52cc 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 e1bb927d0b9fbcb77f576e983ebeadaeb7defd2d..b963623535580cae4b8338f098c3070077bc7123 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 760ba7925ddf52030adf172e2e9fb97b414ee74b..e4aba005961d68e0233afcb14aaffd248157300c 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 e6696309562bf06e45059440438bde4248b529a3..4d9a38b9de62d1127258eb748146e2b5575f674b 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 69aa9544853acd983a9da3254c27054ed04a3e3a..d19282fee6eb1222cea108ff9e5bd86684793939 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 ea0b36fb64411c6aba7dc03f26d8bbc083940ab0..9669076bef75f97397b3d1885d988cea08717450 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 5ed0ccded303897013f7df9c48f2ecd46ecacd57..e99a69313ec5551f8eefa12fc087e71f8fe3ee86 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 b0087901a8015a2f6d37dbd08496054c57d8576f..66aa00631130af19c122921d10f9c443e10c74ba 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 48e9e26ae44994cc670b83729530b94e0883a09b..c5574b35f022d2756451be6760b5388c55363715 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 5ca2412c73580927c1ab68659f384ccfee1c6505..f42ff9450a1dc8a08b174fe99ae5761ac9a33a48 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 22a88c02c001e41269b96463560d98c35191ac59..9ffb51ee2917970caa7247f5a19c5861ebfd65c2 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 79dbf63a6628393fd3cdf87a401debe058af39cc..bd8b449cbb589d7725a2991490755720f5292931 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 42de5503baa39b4809628ffdded8da325ae7d9e0..4870bf5269af17f5612c92e19ea32840e1cd2732 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 ad0fafb3ed175a2e8f2b29e1a5a8bf14b81f5168..3c6965c1ddf7dbef8aef38b36e1543816169d8d4 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 546d48af218133d56a091a1d7b5aa22187680954..c21ab1bea163c1f851b1fa4f4fde232a4424db67 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 eac9194c6a03dc3ce6ffbf2f9485558e6493424c..bccffb208c7796f72d8d267df6da10a5e3fd282b 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 43b8f6c129abdd1fbcb1c4b02f2fff4673099024..d24690f04c22e86306b8aaf1734858577b14e4c8 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 a5a9b503cd50a6b307207691b8458e12535122ea..c39ee4895a0b3a8efe0ab9746455a533958ff9ef 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 46b29d0a03c8a1722a91056d0dd489c31f245119..d8cda40d1aa7cb7b1f14a8f6b5fb8503c3fe389d 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 33e3f535dab761c19b091e06df54e183230c0da7..5351fc054b989426695295cdbd977feeb0d5e94e 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 8a2f2f5a08461fd819e166a2d53144eb9e45416b..4497e1bd5dea5ee8b6c95176d676744725328ff4 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 e6b2e174b61f8177669f5cac6fa6d393b5c7b016..892cbb1a8f253458321e201d405398c35dc06eb9 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 237311956e25d0a64de0627e67627a39f03489ae..ba7577602ff71133fc0a576549f8f586c54aa8ef 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 a7a1f60416a4d1df323e071fcd6a9a871588681b..a4f6214edcda3425a848d844439050aef69310b7 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 43632c676d30ea9269c30aa4bac2425d0b252da8..1dbd2d361211e3c84adc157ad67693ea504b3dd5 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 18df9e19a3335c7f343e359365096daff73f6a0c..a267cd22abea5d60adc692c991e2c0765248a586 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 7f9bfed229f3656c58fcc622b59566326ff29261..b60c958a73538a1ee474e0ee465d04160d8c10bd 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 bd2d4ab1316f35f1965a19404a47905b0f3b4b78..78b6612bbf2ef884a5be2c638880195c5719cff8 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 c26cfcc4a009551f5e007c518f6be132dae4252d..43edfc61f44457cf7917120156b6cb07c926ad43 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 5c7d9fabbd011f6470f5393838d3197f281f8a75..7e40f0d60b712c945fcdbcc690840d91fe72e053 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 e2a8a7157242dae94429340a02359a29e7234f9f..02d51de30fc7da67d1fb670306a3c64b7db804d8 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 8cea28d920f023082b524c8561577fa73ba4ffae..14e7cb56ce7eb4b5eed91e0d66d8c0755d5806c1 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 80a2c8b28e73e9dc78ed66c27b8a73779c40e6fe..45914646716efe60ebac0aafe1f25ce59c4813d0 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 76a806982e562fea4291c1a2432105216a3cd067..d857a952cece8b411df7ee410e2854f90aa54a22 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 24cdff89af1553acbc03cd8d0f7d53d29209c22b..44f92017a1d8f4a060a7efbf06dfb9b03ffb6a57 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 c51304b85ddb53dc76a288963400fd73357a58e6..81d643fc66eee534beda746ddd8a39e8b0429701 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 931299a655711796370b9233adcd2954e576b71e..f8dc8822ba5905e3ddbb5c9ff061cea9deb1b646 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 83a2853ddb1fc5a1095543f58aaa7928b5816470..a7ebdfbdaa0128489428bc3d5b49aa18d94e43a0 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 3f6397fdccc4acf9ca17b5ae9d10e4b512be9bf2..08f8b571f6cfae9a5b594ccd047cf4037f4b78af 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 8eb215d9eaf34745eda6f54fed665b0ca2e84653..b6b41f1677e1742d6f37888f26162772c28786e3 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 546e81e8f6b7088afcf0a87c401b55c138282c48..4e2d1b1a22fadbbbb600e3d66a1e32650e986f52 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 b108a61c0a3537ed06d5cbe0a019a8c30fad71ae..228e16e55c455d34f9fe0e8f564819b60e9d4d2b 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 dcfaa446f21cc729045c146ae78ba78215512bb8..f23a507402713ba75b26c71df9121b686f552d16 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 334d0ef82360dc4a9815880202fb5ec2270e6f28..726489e191c8a7df1700ca83890a49c3a2a4f012 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 85fb1cbef67907872b61962edf910bd3eb891f70..461cf13df10685cb584b08115f96f838cfdb9bbe 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 0486399b461f5454031581f05a47310873d85c42..7f0b7d5d9008dc795c1ad0d61cbf739098e3a09a 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 03ea91fcb6d16158bac3a3a325ad949207ba8eff..42c7d98d58d980195c8c30e0cce145796da8edad 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 571e0637fc691ccc81f80e5546160f3bbfddb3c0..122eace1f3ceb7358f67f56e3f959e158bb799a2 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 204cd1a04eefc28964072edf9968b4d7a31decd5..5239496be53a83647d0efe213d91bb11ed0ee1b4 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 9d00fb8efb2ca8333ec3ae1bdbf2906db7200126..d459607752153e2ed12cc6eab5f410322041631a 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 269efa40214d1b84f07e424836c5ee34f7dc80a7..6171c7edf868efb33082c8df1955eb98a663b646 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 24fc463b913e061cc7483d5a0c7edb508f2f012c..85777bfe72f6a1954f3276ab299f8ed863cd578e 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 5c6d9da624c6c4355dfe124247e2486ee03cce3f..cbd0361d1555e8f448df488939420135d37d2689 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