diff options
Diffstat (limited to 'compiler/GHC/Stg')
-rw-r--r-- | compiler/GHC/Stg/CSE.hs | 6 | ||||
-rw-r--r-- | compiler/GHC/Stg/DepAnal.hs | 12 | ||||
-rw-r--r-- | compiler/GHC/Stg/FVs.hs | 4 | ||||
-rw-r--r-- | compiler/GHC/Stg/Lift.hs | 8 | ||||
-rw-r--r-- | compiler/GHC/Stg/Lift/Analysis.hs | 8 | ||||
-rw-r--r-- | compiler/GHC/Stg/Lift/Monad.hs | 16 | ||||
-rw-r--r-- | compiler/GHC/Stg/Lint.hs | 20 | ||||
-rw-r--r-- | compiler/GHC/Stg/Pipeline.hs | 4 | ||||
-rw-r--r-- | compiler/GHC/Stg/Stats.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Stg/Subst.hs | 4 | ||||
-rw-r--r-- | compiler/GHC/Stg/Syntax.hs | 14 | ||||
-rw-r--r-- | compiler/GHC/Stg/Unarise.hs | 12 |
12 files changed, 55 insertions, 55 deletions
diff --git a/compiler/GHC/Stg/CSE.hs b/compiler/GHC/Stg/CSE.hs index ea9c8e61fa..538556c6af 100644 --- a/compiler/GHC/Stg/CSE.hs +++ b/compiler/GHC/Stg/CSE.hs @@ -89,15 +89,15 @@ module GHC.Stg.CSE (stgCse) where import GhcPrelude import GHC.Core.DataCon -import Id +import GHC.Types.Id import GHC.Stg.Syntax import Outputable -import VarEnv +import GHC.Types.Var.Env import GHC.Core (AltCon(..)) import Data.List (mapAccumL) import Data.Maybe (fromMaybe) import GHC.Core.Map -import NameEnv +import GHC.Types.Name.Env import Control.Monad( (>=>) ) -------------- diff --git a/compiler/GHC/Stg/DepAnal.hs b/compiler/GHC/Stg/DepAnal.hs index 5729128126..90eec24f74 100644 --- a/compiler/GHC/Stg/DepAnal.hs +++ b/compiler/GHC/Stg/DepAnal.hs @@ -5,13 +5,13 @@ module GHC.Stg.DepAnal (depSortStgPgm) where import GhcPrelude import GHC.Stg.Syntax -import Id -import Name (Name, nameIsLocalOrFrom) -import NameEnv +import GHC.Types.Id +import GHC.Types.Name (Name, nameIsLocalOrFrom) +import GHC.Types.Name.Env import Outputable -import UniqSet (nonDetEltsUniqSet) -import VarSet -import Module (Module) +import GHC.Types.Unique.Set (nonDetEltsUniqSet) +import GHC.Types.Var.Set +import GHC.Types.Module (Module) import Data.Graph (SCC (..)) diff --git a/compiler/GHC/Stg/FVs.hs b/compiler/GHC/Stg/FVs.hs index 6bd219d7a3..e323775c5f 100644 --- a/compiler/GHC/Stg/FVs.hs +++ b/compiler/GHC/Stg/FVs.hs @@ -45,8 +45,8 @@ module GHC.Stg.FVs ( import GhcPrelude import GHC.Stg.Syntax -import Id -import VarSet +import GHC.Types.Id +import GHC.Types.Var.Set import GHC.Core ( Tickish(Breakpoint) ) import Outputable import Util diff --git a/compiler/GHC/Stg/Lift.hs b/compiler/GHC/Stg/Lift.hs index a0223707d7..f90ef519fe 100644 --- a/compiler/GHC/Stg/Lift.hs +++ b/compiler/GHC/Stg/Lift.hs @@ -19,17 +19,17 @@ where import GhcPrelude -import BasicTypes +import GHC.Types.Basic import GHC.Driver.Session -import Id +import GHC.Types.Id import GHC.Stg.FVs ( annBindingFreeVars ) import GHC.Stg.Lift.Analysis import GHC.Stg.Lift.Monad import GHC.Stg.Syntax import Outputable -import UniqSupply +import GHC.Types.Unique.Supply import Util -import VarSet +import GHC.Types.Var.Set import Control.Monad ( when ) import Data.Maybe ( isNothing ) diff --git a/compiler/GHC/Stg/Lift/Analysis.hs b/compiler/GHC/Stg/Lift/Analysis.hs index cc477e0eaa..13778237ea 100644 --- a/compiler/GHC/Stg/Lift/Analysis.hs +++ b/compiler/GHC/Stg/Lift/Analysis.hs @@ -23,10 +23,10 @@ module GHC.Stg.Lift.Analysis ( import GhcPrelude import GHC.Platform -import BasicTypes -import Demand +import GHC.Types.Basic +import GHC.Types.Demand import GHC.Driver.Session -import Id +import GHC.Types.Id import GHC.Runtime.Heap.Layout ( WordOff ) import GHC.Stg.Syntax import qualified GHC.StgToCmm.ArgRep as StgToCmm.ArgRep @@ -34,7 +34,7 @@ import qualified GHC.StgToCmm.Closure as StgToCmm.Closure import qualified GHC.StgToCmm.Layout as StgToCmm.Layout import Outputable import Util -import VarSet +import GHC.Types.Var.Set import Data.Maybe ( mapMaybe ) diff --git a/compiler/GHC/Stg/Lift/Monad.hs b/compiler/GHC/Stg/Lift/Monad.hs index 8c0a6d27fc..28ec3e1e69 100644 --- a/compiler/GHC/Stg/Lift/Monad.hs +++ b/compiler/GHC/Stg/Lift/Monad.hs @@ -24,21 +24,21 @@ module GHC.Stg.Lift.Monad ( import GhcPrelude -import BasicTypes -import CostCentre ( isCurrentCCS, dontCareCCS ) +import GHC.Types.Basic +import GHC.Types.CostCentre ( isCurrentCCS, dontCareCCS ) import GHC.Driver.Session import FastString -import Id -import Name +import GHC.Types.Id +import GHC.Types.Name import Outputable import OrdList import GHC.Stg.Subst import GHC.Stg.Syntax import GHC.Core.Type -import UniqSupply +import GHC.Types.Unique.Supply import Util -import VarEnv -import VarSet +import GHC.Types.Var.Env +import GHC.Types.Var.Set import Control.Arrow ( second ) import Control.Monad.Trans.Class @@ -271,7 +271,7 @@ withLiftedBndr abs_ids bndr inner = do let str = "$l" ++ occNameString (getOccName bndr) let ty = mkLamTypes (dVarSetElems abs_ids) (idType bndr) let bndr' - -- See Note [transferPolyIdInfo] in Id.hs. We need to do this at least + -- See Note [transferPolyIdInfo] in GHC.Types.Id. We need to do this at least -- for arity information. = transferPolyIdInfo bndr (dVarSetElems abs_ids) . mkSysLocal (mkFastString str) uniq diff --git a/compiler/GHC/Stg/Lint.hs b/compiler/GHC/Stg/Lint.hs index 3d06815832..bf4cfce443 100644 --- a/compiler/GHC/Stg/Lint.hs +++ b/compiler/GHC/Stg/Lint.hs @@ -42,20 +42,20 @@ import GhcPrelude import GHC.Stg.Syntax import GHC.Driver.Session -import Bag ( Bag, emptyBag, isEmptyBag, snocBag, bagToList ) -import BasicTypes ( TopLevelFlag(..), isTopLevel ) -import CostCentre ( isCurrentCCS ) -import Id ( Id, idType, isJoinId, idName ) -import VarSet +import Bag ( Bag, emptyBag, isEmptyBag, snocBag, bagToList ) +import GHC.Types.Basic ( TopLevelFlag(..), isTopLevel ) +import GHC.Types.CostCentre ( isCurrentCCS ) +import GHC.Types.Id ( Id, idType, isJoinId, idName ) +import GHC.Types.Var.Set import GHC.Core.DataCon -import GHC.Core ( AltCon(..) ) -import Name ( getSrcLoc, nameIsLocalOrFrom ) -import ErrUtils ( MsgDoc, Severity(..), mkLocMessage ) +import GHC.Core ( AltCon(..) ) +import GHC.Types.Name ( getSrcLoc, nameIsLocalOrFrom ) +import ErrUtils ( MsgDoc, Severity(..), mkLocMessage ) import GHC.Core.Type import GHC.Types.RepType -import SrcLoc +import GHC.Types.SrcLoc import Outputable -import Module ( Module ) +import GHC.Types.Module ( Module ) import qualified ErrUtils as Err import Control.Applicative ((<|>)) import Control.Monad diff --git a/compiler/GHC/Stg/Pipeline.hs b/compiler/GHC/Stg/Pipeline.hs index 457466291d..4b463cb95e 100644 --- a/compiler/GHC/Stg/Pipeline.hs +++ b/compiler/GHC/Stg/Pipeline.hs @@ -23,11 +23,11 @@ import GHC.Stg.DepAnal ( depSortStgPgm ) import GHC.Stg.Unarise ( unarise ) import GHC.Stg.CSE ( stgCse ) import GHC.Stg.Lift ( stgLiftLams ) -import Module ( Module ) +import GHC.Types.Module ( Module ) import GHC.Driver.Session import ErrUtils -import UniqSupply +import GHC.Types.Unique.Supply import Outputable import Control.Monad import Control.Monad.IO.Class diff --git a/compiler/GHC/Stg/Stats.hs b/compiler/GHC/Stg/Stats.hs index 8a4fa7561b..c2d546d587 100644 --- a/compiler/GHC/Stg/Stats.hs +++ b/compiler/GHC/Stg/Stats.hs @@ -31,7 +31,7 @@ import GhcPrelude import GHC.Stg.Syntax -import Id (Id) +import GHC.Types.Id (Id) import Panic import Data.Map (Map) diff --git a/compiler/GHC/Stg/Subst.hs b/compiler/GHC/Stg/Subst.hs index aa07c48b36..abbbfb0fd7 100644 --- a/compiler/GHC/Stg/Subst.hs +++ b/compiler/GHC/Stg/Subst.hs @@ -6,8 +6,8 @@ module GHC.Stg.Subst where import GhcPrelude -import Id -import VarEnv +import GHC.Types.Id +import GHC.Types.Var.Env import Control.Monad.Trans.State.Strict import Outputable import Util diff --git a/compiler/GHC/Stg/Syntax.hs b/compiler/GHC/Stg/Syntax.hs index 534cdbfbcb..e31327c06c 100644 --- a/compiler/GHC/Stg/Syntax.hs +++ b/compiler/GHC/Stg/Syntax.hs @@ -64,22 +64,22 @@ module GHC.Stg.Syntax ( import GhcPrelude import GHC.Core ( AltCon, Tickish ) -import CostCentre ( CostCentreStack ) +import GHC.Types.CostCentre ( CostCentreStack ) import Data.ByteString ( ByteString ) import Data.Data ( Data ) import Data.List ( intersperse ) import GHC.Core.DataCon import GHC.Driver.Session -import ForeignCall ( ForeignCall ) -import Id -import VarSet -import Literal ( Literal, literalType ) -import Module ( Module ) +import GHC.Types.ForeignCall ( ForeignCall ) +import GHC.Types.Id +import GHC.Types.Var.Set +import GHC.Types.Literal ( Literal, literalType ) +import GHC.Types.Module ( Module ) import Outputable import GHC.Driver.Packages ( isDynLinkName ) import GHC.Platform import GHC.Core.Ppr( {- instances -} ) -import PrimOp ( PrimOp, PrimCall ) +import PrimOp ( PrimOp, PrimCall ) import GHC.Core.TyCon ( PrimRep(..), TyCon ) import GHC.Core.Type ( Type ) import GHC.Types.RepType ( typePrimRep1 ) diff --git a/compiler/GHC/Stg/Unarise.hs b/compiler/GHC/Stg/Unarise.hs index 98738470b2..6e163ab3e9 100644 --- a/compiler/GHC/Stg/Unarise.hs +++ b/compiler/GHC/Stg/Unarise.hs @@ -202,14 +202,14 @@ module GHC.Stg.Unarise (unarise) where import GhcPrelude -import BasicTypes +import GHC.Types.Basic import GHC.Core import GHC.Core.DataCon import FastString (FastString, mkFastString) -import Id -import Literal +import GHC.Types.Id +import GHC.Types.Literal import GHC.Core.Make (aBSENT_SUM_FIELD_ERROR_ID) -import MkId (voidPrimId, voidArgId) +import GHC.Types.Id.Make (voidPrimId, voidArgId) import MonadUtils (mapAccumLM) import Outputable import GHC.Types.RepType @@ -217,9 +217,9 @@ import GHC.Stg.Syntax import GHC.Core.Type import TysPrim (intPrimTy,wordPrimTy,word64PrimTy) import TysWiredIn -import UniqSupply +import GHC.Types.Unique.Supply import Util -import VarEnv +import GHC.Types.Var.Env import Data.Bifunctor (second) import Data.Maybe (mapMaybe) |