diff options
author | Sylvain Henry <sylvain@haskus.fr> | 2020-02-18 11:08:48 +0100 |
---|---|---|
committer | Marge Bot <ben+marge-bot@smart-cactus.org> | 2020-02-21 20:46:40 -0500 |
commit | 240f5bf6f53515535be5bf3ef7632aa69ae21e3e (patch) | |
tree | dc7be78ca126c66af0aeb9f7944ebfc0ac5a211c | |
parent | be7068a6130f394dcefbcb5d09c2944deca2270d (diff) | |
download | haskell-240f5bf6f53515535be5bf3ef7632aa69ae21e3e.tar.gz |
Modules: Driver (#13009)
submodule updates: nofib, haddock
330 files changed, 679 insertions, 677 deletions
diff --git a/compiler/main/GHC.hs b/compiler/GHC.hs index b15803eed1..9200f27809 100644 --- a/compiler/main/GHC.hs +++ b/compiler/GHC.hs @@ -288,7 +288,7 @@ module GHC ( {- ToDo: - * inline bits of HscMain here to simplify layering: hscTcExpr, hscStmt. + * inline bits of GHC.Driver.Main here to simplify layering: hscTcExpr, hscStmt. -} #include "HsVersions.h" @@ -302,15 +302,15 @@ import GHC.Runtime.Interpreter import GHCi.RemoteTypes import PprTyThing ( pprFamInst ) -import HscMain -import GhcMake -import DriverPipeline ( compileOne' ) -import GhcMonad +import GHC.Driver.Main +import GHC.Driver.Make +import GHC.Driver.Pipeline ( compileOne' ) +import GHC.Driver.Monad import TcRnMonad ( finalSafeMode, fixSafeInstances, initIfaceTcRn ) import GHC.Iface.Load ( loadSysInterface ) import TcRnTypes import Predicate -import Packages +import GHC.Driver.Packages import NameSet import RdrName import GHC.Hs @@ -329,11 +329,11 @@ import FamInstEnv ( FamInst ) import SrcLoc import CoreSyn import GHC.Iface.Tidy -import DriverPhases ( Phase(..), isHaskellSrcFilename ) -import Finder -import HscTypes -import CmdLineParser -import DynFlags hiding (WarnReason(..)) +import GHC.Driver.Phases ( Phase(..), isHaskellSrcFilename ) +import GHC.Driver.Finder +import GHC.Driver.Types +import GHC.Driver.CmdLine +import GHC.Driver.Session hiding (WarnReason(..)) import SysTools import SysTools.BaseDir import Annotations @@ -1364,7 +1364,7 @@ getModuleSourceAndFlags mod = do -- | Return module source as token stream, including comments. -- -- The module must be in the module graph and its source must be available. --- Throws a 'HscTypes.SourceError' on parse error. +-- Throws a 'GHC.Driver.Types.SourceError' on parse error. getTokenStream :: GhcMonad m => Module -> m [Located Token] getTokenStream mod = do (sourceFile, source, flags) <- getModuleSourceAndFlags mod diff --git a/compiler/GHC/ByteCode/Asm.hs b/compiler/GHC/ByteCode/Asm.hs index 95e728c2a6..79b0bc2766 100644 --- a/compiler/GHC/ByteCode/Asm.hs +++ b/compiler/GHC/ByteCode/Asm.hs @@ -23,7 +23,7 @@ import GHC.ByteCode.Types import GHCi.RemoteTypes import GHC.Runtime.Interpreter -import HscTypes +import GHC.Driver.Types import Name import NameSet import Literal @@ -31,7 +31,7 @@ import TyCon import FastString import GHC.StgToCmm.Layout ( ArgRep(..) ) import GHC.Runtime.Heap.Layout -import DynFlags +import GHC.Driver.Session import Outputable import GHC.Platform import Util diff --git a/compiler/GHC/ByteCode/InfoTable.hs b/compiler/GHC/ByteCode/InfoTable.hs index 40a107756d..80a259d94d 100644 --- a/compiler/GHC/ByteCode/InfoTable.hs +++ b/compiler/GHC/ByteCode/InfoTable.hs @@ -13,8 +13,8 @@ import GhcPrelude import GHC.ByteCode.Types import GHC.Runtime.Interpreter -import DynFlags -import HscTypes +import GHC.Driver.Session +import GHC.Driver.Types import Name ( Name, getName ) import NameEnv import DataCon ( DataCon, dataConRepArgTys, dataConIdentity ) diff --git a/compiler/GHC/ByteCode/Linker.hs b/compiler/GHC/ByteCode/Linker.hs index 69bdb63a91..1e77b0967e 100644 --- a/compiler/GHC/ByteCode/Linker.hs +++ b/compiler/GHC/ByteCode/Linker.hs @@ -27,7 +27,7 @@ import SizedSeq import GHC.Runtime.Interpreter import GHC.ByteCode.Types -import HscTypes +import GHC.Driver.Types import Name import NameEnv import PrimOp diff --git a/compiler/GHC/Cmm/CLabel.hs b/compiler/GHC/Cmm/CLabel.hs index 8cac0aa5dd..f3cf8019d0 100644 --- a/compiler/GHC/Cmm/CLabel.hs +++ b/compiler/GHC/Cmm/CLabel.hs @@ -118,7 +118,7 @@ import GhcPrelude import IdInfo import BasicTypes import {-# SOURCE #-} GHC.Cmm.BlockId (BlockId, mkBlockId) -import Packages +import GHC.Driver.Packages import Module import Name import Unique @@ -126,7 +126,7 @@ import PrimOp import CostCentre import Outputable import FastString -import DynFlags +import GHC.Driver.Session import GHC.Platform import UniqSet import Util diff --git a/compiler/GHC/Cmm/CallConv.hs b/compiler/GHC/Cmm/CallConv.hs index db9603c524..40f348f9e0 100644 --- a/compiler/GHC/Cmm/CallConv.hs +++ b/compiler/GHC/Cmm/CallConv.hs @@ -12,7 +12,7 @@ import GHC.Runtime.Heap.Layout import GHC.Cmm (Convention(..)) import GHC.Cmm.Ppr () -- For Outputable instances -import DynFlags +import GHC.Driver.Session import GHC.Platform import Outputable diff --git a/compiler/GHC/Cmm/Expr.hs b/compiler/GHC/Cmm/Expr.hs index 3b4f0156a0..9be4200f85 100644 --- a/compiler/GHC/Cmm/Expr.hs +++ b/compiler/GHC/Cmm/Expr.hs @@ -36,7 +36,7 @@ import GHC.Cmm.BlockId import GHC.Cmm.CLabel import GHC.Cmm.MachOp import GHC.Cmm.Type -import DynFlags +import GHC.Driver.Session import Outputable (panic) import Unique diff --git a/compiler/GHC/Cmm/Graph.hs b/compiler/GHC/Cmm/Graph.hs index 1d8b44776d..c07f694897 100644 --- a/compiler/GHC/Cmm/Graph.hs +++ b/compiler/GHC/Cmm/Graph.hs @@ -31,7 +31,7 @@ import GHC.Cmm.Switch (SwitchTargets) import GHC.Cmm.Dataflow.Block import GHC.Cmm.Dataflow.Graph import GHC.Cmm.Dataflow.Label -import DynFlags +import GHC.Driver.Session import FastString import ForeignCall import OrdList diff --git a/compiler/GHC/Cmm/Info.hs b/compiler/GHC/Cmm/Info.hs index 6948f78969..6b2a3d82c6 100644 --- a/compiler/GHC/Cmm/Info.hs +++ b/compiler/GHC/Cmm/Info.hs @@ -46,7 +46,7 @@ import GHC.Cmm.Dataflow.Collections import GHC.Platform import Maybes -import DynFlags +import GHC.Driver.Session import ErrUtils (withTimingSilent) import Panic import UniqSupply diff --git a/compiler/GHC/Cmm/Info/Build.hs b/compiler/GHC/Cmm/Info/Build.hs index 92619b8959..54a7d8fb91 100644 --- a/compiler/GHC/Cmm/Info/Build.hs +++ b/compiler/GHC/Cmm/Info/Build.hs @@ -24,7 +24,7 @@ import Digraph import GHC.Cmm.CLabel import GHC.Cmm import GHC.Cmm.Utils -import DynFlags +import GHC.Driver.Session import Maybes import Outputable import GHC.Runtime.Heap.Layout diff --git a/compiler/GHC/Cmm/LayoutStack.hs b/compiler/GHC/Cmm/LayoutStack.hs index b34de95982..2b6051dd38 100644 --- a/compiler/GHC/Cmm/LayoutStack.hs +++ b/compiler/GHC/Cmm/LayoutStack.hs @@ -29,7 +29,7 @@ import Maybes import UniqFM import Util -import DynFlags +import GHC.Driver.Session import FastString import Outputable hiding ( isEmpty ) import qualified Data.Set as Set diff --git a/compiler/GHC/Cmm/Lint.hs b/compiler/GHC/Cmm/Lint.hs index d70fed3b9e..a6bec1f187 100644 --- a/compiler/GHC/Cmm/Lint.hs +++ b/compiler/GHC/Cmm/Lint.hs @@ -23,7 +23,7 @@ import GHC.Cmm.Liveness import GHC.Cmm.Switch (switchTargetsToList) import GHC.Cmm.Ppr () -- For Outputable instances import Outputable -import DynFlags +import GHC.Driver.Session import Control.Monad (ap) diff --git a/compiler/GHC/Cmm/Liveness.hs b/compiler/GHC/Cmm/Liveness.hs index 2b598f52e5..10d4ca8dfd 100644 --- a/compiler/GHC/Cmm/Liveness.hs +++ b/compiler/GHC/Cmm/Liveness.hs @@ -14,7 +14,7 @@ where import GhcPrelude -import DynFlags +import GHC.Driver.Session import GHC.Cmm.BlockId import GHC.Cmm import GHC.Cmm.Ppr.Expr () -- For Outputable instances diff --git a/compiler/GHC/Cmm/MachOp.hs b/compiler/GHC/Cmm/MachOp.hs index a887477028..d811d4808f 100644 --- a/compiler/GHC/Cmm/MachOp.hs +++ b/compiler/GHC/Cmm/MachOp.hs @@ -32,7 +32,7 @@ import GhcPrelude import GHC.Cmm.Type import Outputable -import DynFlags +import GHC.Driver.Session ----------------------------------------------------------------------------- -- MachOp diff --git a/compiler/GHC/Cmm/Monad.hs b/compiler/GHC/Cmm/Monad.hs index eccaf72676..d6c8a5b3cc 100644 --- a/compiler/GHC/Cmm/Monad.hs +++ b/compiler/GHC/Cmm/Monad.hs @@ -17,7 +17,7 @@ import GhcPrelude import Control.Monad -import DynFlags +import GHC.Driver.Session import Lexer newtype PD a = PD { unPD :: DynFlags -> PState -> ParseResult a } diff --git a/compiler/GHC/Cmm/Node.hs b/compiler/GHC/Cmm/Node.hs index f7cee80145..f26fb2c9d9 100644 --- a/compiler/GHC/Cmm/Node.hs +++ b/compiler/GHC/Cmm/Node.hs @@ -31,7 +31,7 @@ import GhcPrelude hiding (succ) import GHC.Platform.Regs import GHC.Cmm.Expr import GHC.Cmm.Switch -import DynFlags +import GHC.Driver.Session import FastString import ForeignCall import Outputable diff --git a/compiler/GHC/Cmm/Opt.hs b/compiler/GHC/Cmm/Opt.hs index 1db37ae58c..7dd43852a6 100644 --- a/compiler/GHC/Cmm/Opt.hs +++ b/compiler/GHC/Cmm/Opt.hs @@ -17,7 +17,7 @@ import GhcPrelude import GHC.Cmm.Utils import GHC.Cmm -import DynFlags +import GHC.Driver.Session import Util import Outputable diff --git a/compiler/GHC/Cmm/Parser.y b/compiler/GHC/Cmm/Parser.y index 2e6762e68a..69a2a9347e 100644 --- a/compiler/GHC/Cmm/Parser.y +++ b/compiler/GHC/Cmm/Parser.y @@ -242,7 +242,7 @@ import Literal import Unique import UniqFM import SrcLoc -import DynFlags +import GHC.Driver.Session import ErrUtils import StringBuffer import FastString diff --git a/compiler/GHC/Cmm/Pipeline.hs b/compiler/GHC/Cmm/Pipeline.hs index 9fd484fdb2..88db550d8a 100644 --- a/compiler/GHC/Cmm/Pipeline.hs +++ b/compiler/GHC/Cmm/Pipeline.hs @@ -23,9 +23,9 @@ import GHC.Cmm.Sink import GHC.Cmm.Dataflow.Collections import UniqSupply -import DynFlags +import GHC.Driver.Session import ErrUtils -import HscTypes +import GHC.Driver.Types import Control.Monad import Outputable import GHC.Platform diff --git a/compiler/GHC/Cmm/Ppr/Decl.hs b/compiler/GHC/Cmm/Ppr/Decl.hs index e91c4b6277..6c19d5f7a6 100644 --- a/compiler/GHC/Cmm/Ppr/Decl.hs +++ b/compiler/GHC/Cmm/Ppr/Decl.hs @@ -43,7 +43,7 @@ import GhcPrelude import GHC.Cmm.Ppr.Expr import GHC.Cmm -import DynFlags +import GHC.Driver.Session import Outputable import FastString diff --git a/compiler/GHC/Cmm/ProcPoint.hs b/compiler/GHC/Cmm/ProcPoint.hs index 1e4b70bd23..42bd342e86 100644 --- a/compiler/GHC/Cmm/ProcPoint.hs +++ b/compiler/GHC/Cmm/ProcPoint.hs @@ -11,7 +11,7 @@ where import GhcPrelude hiding (last, unzip, succ, zip) -import DynFlags +import GHC.Driver.Session import GHC.Cmm.BlockId import GHC.Cmm.CLabel import GHC.Cmm diff --git a/compiler/GHC/Cmm/Sink.hs b/compiler/GHC/Cmm/Sink.hs index 8e231df300..ceb4f874ee 100644 --- a/compiler/GHC/Cmm/Sink.hs +++ b/compiler/GHC/Cmm/Sink.hs @@ -16,7 +16,7 @@ import GHC.Cmm.Dataflow.Graph import GHC.Platform.Regs import GHC.Platform (isARM, platformArch) -import DynFlags +import GHC.Driver.Session import Unique import UniqFM diff --git a/compiler/GHC/Cmm/Switch.hs b/compiler/GHC/Cmm/Switch.hs index ea7932ca17..f297bd8b5e 100644 --- a/compiler/GHC/Cmm/Switch.hs +++ b/compiler/GHC/Cmm/Switch.hs @@ -15,7 +15,7 @@ module GHC.Cmm.Switch ( import GhcPrelude import Outputable -import DynFlags +import GHC.Driver.Session import GHC.Cmm.Dataflow.Label (Label) import Data.Maybe diff --git a/compiler/GHC/Cmm/Switch/Implement.hs b/compiler/GHC/Cmm/Switch/Implement.hs index 859fe81b8d..2074c465ad 100644 --- a/compiler/GHC/Cmm/Switch/Implement.hs +++ b/compiler/GHC/Cmm/Switch/Implement.hs @@ -12,7 +12,7 @@ import GHC.Cmm import GHC.Cmm.Utils import GHC.Cmm.Switch import UniqSupply -import DynFlags +import GHC.Driver.Session import MonadUtils (concatMapM) -- diff --git a/compiler/GHC/Cmm/Type.hs b/compiler/GHC/Cmm/Type.hs index 867a260078..2fb4ea61a7 100644 --- a/compiler/GHC/Cmm/Type.hs +++ b/compiler/GHC/Cmm/Type.hs @@ -31,7 +31,7 @@ where import GhcPrelude -import DynFlags +import GHC.Driver.Session import FastString import Outputable diff --git a/compiler/GHC/Cmm/Utils.hs b/compiler/GHC/Cmm/Utils.hs index c62f7eb3df..5a34ae45e2 100644 --- a/compiler/GHC/Cmm/Utils.hs +++ b/compiler/GHC/Cmm/Utils.hs @@ -80,7 +80,7 @@ import GHC.Cmm import GHC.Cmm.BlockId import GHC.Cmm.CLabel import Outputable -import DynFlags +import GHC.Driver.Session import Unique import GHC.Platform.Regs diff --git a/compiler/GHC/CmmToC.hs b/compiler/GHC/CmmToC.hs index 25b32be0d0..f7245f5c30 100644 --- a/compiler/GHC/CmmToC.hs +++ b/compiler/GHC/CmmToC.hs @@ -40,7 +40,7 @@ import GHC.Cmm.Switch -- Utils import CPrim -import DynFlags +import GHC.Driver.Session import FastString import Outputable import GHC.Platform diff --git a/compiler/GHC/CmmToLlvm.hs b/compiler/GHC/CmmToLlvm.hs index f84c2901a5..d89b8e93cf 100644 --- a/compiler/GHC/CmmToLlvm.hs +++ b/compiler/GHC/CmmToLlvm.hs @@ -29,7 +29,7 @@ import GHC.Cmm.Dataflow.Collections import GHC.Cmm.Ppr import BufWrite -import DynFlags +import GHC.Driver.Session import GHC.Platform ( platformArch, Arch(..) ) import ErrUtils import FastString diff --git a/compiler/GHC/CmmToLlvm/Base.hs b/compiler/GHC/CmmToLlvm/Base.hs index 5cfef04029..9d97f3eb3c 100644 --- a/compiler/GHC/CmmToLlvm/Base.hs +++ b/compiler/GHC/CmmToLlvm/Base.hs @@ -48,7 +48,7 @@ import GHC.CmmToLlvm.Regs import GHC.Cmm.CLabel import GHC.Platform.Regs ( activeStgRegs ) -import DynFlags +import GHC.Driver.Session import FastString import GHC.Cmm hiding ( succ ) import GHC.Cmm.Utils (regsOverlap) diff --git a/compiler/GHC/CmmToLlvm/CodeGen.hs b/compiler/GHC/CmmToLlvm/CodeGen.hs index 947ba31f35..62ebeb9ba7 100644 --- a/compiler/GHC/CmmToLlvm/CodeGen.hs +++ b/compiler/GHC/CmmToLlvm/CodeGen.hs @@ -25,7 +25,7 @@ import GHC.Cmm.Dataflow.Block import GHC.Cmm.Dataflow.Graph import GHC.Cmm.Dataflow.Collections -import DynFlags +import GHC.Driver.Session import FastString import ForeignCall import Outputable hiding (panic, pprPanic) diff --git a/compiler/GHC/CmmToLlvm/Data.hs b/compiler/GHC/CmmToLlvm/Data.hs index b20c9bd360..7a6320f947 100644 --- a/compiler/GHC/CmmToLlvm/Data.hs +++ b/compiler/GHC/CmmToLlvm/Data.hs @@ -17,7 +17,7 @@ import GHC.CmmToLlvm.Base import GHC.Cmm.BlockId import GHC.Cmm.CLabel import GHC.Cmm -import DynFlags +import GHC.Driver.Session import GHC.Platform import FastString diff --git a/compiler/GHC/CmmToLlvm/Mangler.hs b/compiler/GHC/CmmToLlvm/Mangler.hs index 1cdad2009f..6bf27267d7 100644 --- a/compiler/GHC/CmmToLlvm/Mangler.hs +++ b/compiler/GHC/CmmToLlvm/Mangler.hs @@ -13,7 +13,7 @@ module GHC.CmmToLlvm.Mangler ( llvmFixupAsm ) where import GhcPrelude -import DynFlags ( DynFlags, targetPlatform ) +import GHC.Driver.Session ( DynFlags, targetPlatform ) import GHC.Platform ( platformArch, Arch(..) ) import ErrUtils ( withTiming ) import Outputable ( text ) diff --git a/compiler/GHC/CmmToLlvm/Regs.hs b/compiler/GHC/CmmToLlvm/Regs.hs index 60c27c8f44..af2a88c4c9 100644 --- a/compiler/GHC/CmmToLlvm/Regs.hs +++ b/compiler/GHC/CmmToLlvm/Regs.hs @@ -16,7 +16,7 @@ import GhcPrelude import GHC.Llvm import GHC.Cmm.Expr -import DynFlags +import GHC.Driver.Session import FastString import Outputable ( panic ) import Unique diff --git a/compiler/GHC/CoreToByteCode.hs b/compiler/GHC/CoreToByteCode.hs index 318364fd7c..a2b18601ca 100644 --- a/compiler/GHC/CoreToByteCode.hs +++ b/compiler/GHC/CoreToByteCode.hs @@ -22,7 +22,7 @@ import GHC.Runtime.Interpreter import GHCi.FFI import GHCi.RemoteTypes import BasicTypes -import DynFlags +import GHC.Driver.Session import Outputable import GHC.Platform import Name @@ -30,7 +30,7 @@ import MkId import Id import Var ( updateVarType ) import ForeignCall -import HscTypes +import GHC.Driver.Types import CoreUtils import CoreSyn import PprCore diff --git a/compiler/GHC/CoreToStg.hs b/compiler/GHC/CoreToStg.hs index 2e922b6de6..ead7a12da0 100644 --- a/compiler/GHC/CoreToStg.hs +++ b/compiler/GHC/CoreToStg.hs @@ -41,7 +41,7 @@ import Outputable import MonadUtils import FastString import Util -import DynFlags +import GHC.Driver.Session import ForeignCall import Demand ( isUsedOnce ) import PrimOp ( PrimCall(..), primOpWrapperId ) diff --git a/compiler/GHC/CoreToStg/Prep.hs b/compiler/GHC/CoreToStg/Prep.hs index edfe9cc363..300c95f6df 100644 --- a/compiler/GHC/CoreToStg/Prep.hs +++ b/compiler/GHC/CoreToStg/Prep.hs @@ -21,7 +21,7 @@ import GhcPrelude import OccurAnal -import HscTypes +import GHC.Driver.Types import PrelNames import MkId ( realWorldPrimId ) import CoreUtils @@ -50,7 +50,7 @@ import UniqSupply import Maybes import OrdList import ErrUtils -import DynFlags +import GHC.Driver.Session import Util import Outputable import FastString diff --git a/compiler/GHC/Data/Bitmap.hs b/compiler/GHC/Data/Bitmap.hs index c778a575f8..1b93d6000d 100644 --- a/compiler/GHC/Data/Bitmap.hs +++ b/compiler/GHC/Data/Bitmap.hs @@ -18,7 +18,7 @@ module GHC.Data.Bitmap ( import GhcPrelude import GHC.Runtime.Heap.Layout -import DynFlags +import GHC.Driver.Session import Util import Data.Bits diff --git a/compiler/backpack/DriverBkp.hs b/compiler/GHC/Driver/Backpack.hs index 4246a04dd3..e5364e3d3f 100644 --- a/compiler/backpack/DriverBkp.hs +++ b/compiler/GHC/Driver/Backpack.hs @@ -14,42 +14,42 @@ -- it builds and doesn't serialize out the database contents. -- But it's still handy for constructing tests. -module DriverBkp (doBackpack) where +module GHC.Driver.Backpack (doBackpack) where #include "HsVersions.h" import GhcPrelude -- In a separate module because it hooks into the parser. -import BkpSyn +import GHC.Driver.Backpack.Syntax import ApiAnnotation import GHC hiding (Failed, Succeeded) -import Packages +import GHC.Driver.Packages import Parser import Lexer -import GhcMonad -import DynFlags +import GHC.Driver.Monad +import GHC.Driver.Session import TcRnMonad import TcRnDriver import Module -import HscTypes +import GHC.Driver.Types import StringBuffer import FastString import ErrUtils import SrcLoc -import HscMain +import GHC.Driver.Main import UniqFM import UniqDFM import Outputable import Maybes import HeaderInfo import GHC.Iface.Utils -import GhcMake +import GHC.Driver.Make import UniqDSet import PrelNames import BasicTypes hiding (SuccessFlag(..)) -import Finder +import GHC.Driver.Finder import Util import qualified GHC.LanguageExtensions as LangExt @@ -75,7 +75,7 @@ doBackpack [src_filename] = do src_opts <- liftIO $ getOptionsFromFile dflags1 src_filename (dflags, unhandled_flags, warns) <- liftIO $ parseDynamicFilePragma dflags1 src_opts modifySession (\hsc_env -> hsc_env {hsc_dflags = dflags}) - -- Cribbed from: preprocessFile / DriverPipeline + -- Cribbed from: preprocessFile / GHC.Driver.Pipeline liftIO $ checkProcessArgsResult dflags unhandled_flags liftIO $ handleFlagWarnings dflags warns -- TODO: Preprocessing not implemented @@ -264,7 +264,7 @@ buildUnit session cid insts lunit = do -- Build dependencies OR make sure they make sense. BUT NOTE, -- we can only check the ones that are fully filled; the rest -- we have to defer until we've typechecked our local signature. - -- TODO: work this into GhcMake!! + -- TODO: work this into GHC.Driver.Make!! forM_ (zip [1..] deps0) $ \(i, dep) -> case session of TcSession -> return () @@ -629,14 +629,14 @@ convertHsModuleId (HsModuleId (L _ hsuid) (L _ modname)) = mkModule (convertHsUn ************************************************************************ -} --- | This is our version of GhcMake.downsweep, but with a few modifications: +-- | This is our version of GHC.Driver.Make.downsweep, but with a few modifications: -- -- 1. Every module is required to be mentioned, so we don't do any funny -- business with targets or recursively grabbing dependencies. (We -- could support this in principle). -- 2. We support inline modules, whose summary we have to synthesize ourself. -- --- We don't bother trying to support GhcMake for now, it's more trouble +-- We don't bother trying to support GHC.Driver.Make for now, it's more trouble -- than it's worth for inline modules. hsunitModuleGraph :: DynFlags -> HsUnit HsComponentId -> BkpM ModuleGraph hsunitModuleGraph dflags unit = do @@ -747,7 +747,7 @@ hsModuleToModSummary pn hsc_src modname let imps = hsmodImports (unLoc hsmod) loc = getLoc hsmod hsc_env <- getSession - -- Sort of the same deal as in DriverPipeline's getLocation + -- Sort of the same deal as in GHC.Driver.Pipeline's getLocation -- Use the PACKAGE NAME to find the location let PackageName unit_fs = pn dflags = hsc_dflags hsc_env @@ -768,7 +768,7 @@ hsModuleToModSummary pn hsc_src modname let location = case hsc_src of HsBootFile -> addBootSuffixLocnOut location0 _ -> location0 - -- This duplicates a pile of logic in GhcMake + -- This duplicates a pile of logic in GHC.Driver.Make env <- getBkpEnv time <- liftIO $ getModificationUTCTime (bkp_filename env) hi_timestamp <- liftIO $ modificationTimeIfExists (ml_hi_file location) diff --git a/compiler/backpack/BkpSyn.hs b/compiler/GHC/Driver/Backpack/Syntax.hs index fcc0160899..709427ebd0 100644 --- a/compiler/backpack/BkpSyn.hs +++ b/compiler/GHC/Driver/Backpack/Syntax.hs @@ -1,7 +1,7 @@ -- | This is the syntax for bkp files which are parsed in 'ghc --backpack' -- mode. This syntax is used purely for testing purposes. -module BkpSyn ( +module GHC.Driver.Backpack.Syntax ( -- * Backpack abstract syntax HsUnitId(..), LHsUnitId, @@ -18,7 +18,7 @@ module BkpSyn ( import GhcPrelude -import DriverPhases +import GHC.Driver.Phases import GHC.Hs import SrcLoc import Outputable diff --git a/compiler/main/CmdLineParser.hs b/compiler/GHC/Driver/CmdLine.hs index d2cc56f033..9b71e3d3fb 100644 --- a/compiler/main/CmdLineParser.hs +++ b/compiler/GHC/Driver/CmdLine.hs @@ -11,7 +11,7 @@ -- ------------------------------------------------------------------------------- -module CmdLineParser +module GHC.Driver.CmdLine ( processArgs, OptKind(..), GhcFlagMode(..), CmdLineP(..), getCmdLineState, putCmdLineState, diff --git a/compiler/main/CodeOutput.hs b/compiler/GHC/Driver/CodeOutput.hs index de5452740e..e52d3216d5 100644 --- a/compiler/main/CodeOutput.hs +++ b/compiler/GHC/Driver/CodeOutput.hs @@ -6,7 +6,7 @@ {-# LANGUAGE CPP #-} -module CodeOutput( codeOutput, outputForeignStubs ) where +module GHC.Driver.CodeOutput ( codeOutput, outputForeignStubs ) where #include "HsVersions.h" @@ -17,13 +17,13 @@ import GHC.CmmToLlvm ( llvmCodeGen ) import UniqSupply ( mkSplitUniqSupply ) -import Finder ( mkStubPaths ) -import GHC.CmmToC ( writeC ) -import GHC.Cmm.Lint ( cmmLint ) -import Packages +import GHC.Driver.Finder ( mkStubPaths ) +import GHC.CmmToC ( writeC ) +import GHC.Cmm.Lint ( cmmLint ) +import GHC.Driver.Packages import GHC.Cmm ( RawCmmGroup ) -import HscTypes -import DynFlags +import GHC.Driver.Types +import GHC.Driver.Session import Stream ( Stream ) import qualified Stream import FileCleanup diff --git a/compiler/main/Finder.hs b/compiler/GHC/Driver/Finder.hs index 05d99a6a21..c7c9c1af1f 100644 --- a/compiler/main/Finder.hs +++ b/compiler/GHC/Driver/Finder.hs @@ -6,7 +6,7 @@ {-# LANGUAGE CPP #-} -module Finder ( +module GHC.Driver.Finder ( flushFinderCaches, FindResult(..), findImportedModule, @@ -36,12 +36,12 @@ module Finder ( import GhcPrelude import Module -import HscTypes -import Packages +import GHC.Driver.Types +import GHC.Driver.Packages import FastString import Util import PrelNames ( gHC_PRIM ) -import DynFlags +import GHC.Driver.Session import Outputable import Maybes ( expectJust ) diff --git a/compiler/main/Hooks.hs b/compiler/GHC/Driver/Hooks.hs index 064f96c33e..027d8831b7 100644 --- a/compiler/main/Hooks.hs +++ b/compiler/GHC/Driver/Hooks.hs @@ -5,32 +5,34 @@ {-# LANGUAGE CPP, RankNTypes #-} -module Hooks ( Hooks - , emptyHooks - , lookupHook - , getHooked - -- the hooks: - , dsForeignsHook - , tcForeignImportsHook - , tcForeignExportsHook - , hscFrontendHook - , hscCompileCoreExprHook - , ghcPrimIfaceHook - , runPhaseHook - , runMetaHook - , linkHook - , runRnSpliceHook - , getValueSafelyHook - , createIservProcessHook - , stgToCmmHook - , cmmToRawCmmHook - ) where +module GHC.Driver.Hooks + ( Hooks + , emptyHooks + , lookupHook + , getHooked + -- the hooks: + , dsForeignsHook + , tcForeignImportsHook + , tcForeignExportsHook + , hscFrontendHook + , hscCompileCoreExprHook + , ghcPrimIfaceHook + , runPhaseHook + , runMetaHook + , linkHook + , runRnSpliceHook + , getValueSafelyHook + , createIservProcessHook + , stgToCmmHook + , cmmToRawCmmHook + ) +where import GhcPrelude -import DynFlags -import PipelineMonad -import HscTypes +import GHC.Driver.Session +import GHC.Driver.Pipeline.Monad +import GHC.Driver.Types import GHC.Hs.Decls import GHC.Hs.Binds import GHC.Hs.Expr diff --git a/compiler/main/Hooks.hs-boot b/compiler/GHC/Driver/Hooks.hs-boot index f0246ef941..40ee5560ee 100644 --- a/compiler/main/Hooks.hs-boot +++ b/compiler/GHC/Driver/Hooks.hs-boot @@ -1,4 +1,4 @@ -module Hooks where +module GHC.Driver.Hooks where import GhcPrelude () diff --git a/compiler/main/HscMain.hs b/compiler/GHC/Driver/Main.hs index 879d8a05ec..e5c030f741 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/GHC/Driver/Main.hs @@ -7,7 +7,7 @@ -- -- This module implements compilation of a Haskell source. It is -- /not/ concerned with preprocessing of source files; this is handled --- in "DriverPipeline". +-- in GHC.Driver.Pipeline -- -- There are various entry points depending on what mode we're in: -- "batch" mode (@--make@), "one-shot" mode (@-c@, @-S@ etc.), and @@ -30,7 +30,7 @@ -- ------------------------------------------------------------------------------- -module HscMain +module GHC.Driver.Main ( -- * Making an HscEnv newHscEnv @@ -104,7 +104,7 @@ import Control.Concurrent import ApiAnnotation import Module -import Packages +import GHC.Driver.Packages import RdrName import GHC.Hs import GHC.Hs.Dump @@ -140,23 +140,23 @@ import GHC.Cmm.Parser ( parseCmmFile ) import GHC.Cmm.Info.Build import GHC.Cmm.Pipeline import GHC.Cmm.Info -import CodeOutput +import GHC.Driver.CodeOutput import InstEnv import FamInstEnv import Fingerprint ( Fingerprint ) -import Hooks +import GHC.Driver.Hooks import TcEnv import PrelNames -import Plugins +import GHC.Driver.Plugins import GHC.Runtime.Loader ( initializePlugins ) -import DynFlags +import GHC.Driver.Session import ErrUtils import Outputable import NameEnv import HscStats ( ppSourceStats ) -import HscTypes +import GHC.Driver.Types import FastString import UniqSupply import Bag @@ -818,7 +818,7 @@ finish summary tc_result mb_old_hash = do liftIO $ tidyProgram hsc_env simplified_guts let !partial_iface = - {-# SCC "HscMain.mkPartialIface" #-} + {-# SCC "GHC.Driver.Main.mkPartialIface" #-} -- This `force` saves 2M residency in test T10370 -- See Note [Avoiding space leaks in toIface*] for details. force (mkPartialIface hsc_env details simplified_guts) @@ -848,11 +848,11 @@ finish summary tc_result mb_old_hash = do Note [Writing interface files] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -We write interface files in HscMain.hs and DriverPipeline.hs using +We write interface files in GHC.Driver.Main and GHC.Driver.Pipeline using hscMaybeWriteIface, but only once per compilation (twice with dynamic-too). * If a compilation does NOT require (re)compilation of the hard code we call - hscMaybeWriteIface inside HscMain:finish. + hscMaybeWriteIface inside GHC.Driver.Main:finish. * If we run in One Shot mode and target bytecode we write it in compileOne' * Otherwise we must be compiling to regular hard code and require recompilation. In this case we create the interface file inside RunPhase using the interface @@ -1061,7 +1061,7 @@ checkSafeImports tcg_env pkgReqs = imp_trust_pkgs impInfo -- [UnitId] condense :: (Module, [ImportedModsVal]) -> Hsc (Module, SrcSpan, IsSafeImport) - condense (_, []) = panic "HscMain.condense: Pattern match failure!" + condense (_, []) = panic "GHC.Driver.Main.condense: Pattern match failure!" condense (m, x:xs) = do imv <- foldlM cond' x xs return (m, imv_span imv, imv_is_safe imv) @@ -1621,7 +1621,7 @@ you run it you get a list of HValues that should be the same length as the list of names; add them to the ClosureEnv. A naked expression returns a singleton Name [it]. The stmt is lifted into the -IO monad as explained in Note [Interactively-bound Ids in GHCi] in HscTypes +IO monad as explained in Note [Interactively-bound Ids in GHCi] in GHC.Driver.Types -} -- | Compile a stmt all the way to an HValue, but don't run it @@ -1763,7 +1763,7 @@ hscParsedDecls hsc_env decls = runInteractiveHsc hsc_env $ do -- We only need to keep around the external bindings -- (as decided by GHC.Iface.Tidy), since those are the only ones -- that might later be looked up by name. But we can exclude - -- - DFunIds, which are in 'cls_insts' (see Note [ic_tythings] in HscTypes + -- - DFunIds, which are in 'cls_insts' (see Note [ic_tythings] in GHC.Driver.Types -- - Implicit Ids, which are implicit in tcs -- c.f. TcRnDriver.runTcInteractive, which reconstructs the TypeEnv diff --git a/compiler/main/GhcMake.hs b/compiler/GHC/Driver/Make.hs index 8bb2550d76..e1aa392771 100644 --- a/compiler/main/GhcMake.hs +++ b/compiler/GHC/Driver/Make.hs @@ -11,7 +11,7 @@ -- by --make and GHCi. -- -- ----------------------------------------------------------------------------- -module GhcMake( +module GHC.Driver.Make ( depanal, depanalE, depanalPartial, load, load', LoadHowMuch(..), @@ -37,18 +37,18 @@ import GhcPrelude import qualified GHC.Runtime.Linker as Linker -import DriverPhases -import DriverPipeline -import DynFlags +import GHC.Driver.Phases +import GHC.Driver.Pipeline +import GHC.Driver.Session import ErrUtils -import Finder -import GhcMonad +import GHC.Driver.Finder +import GHC.Driver.Monad import HeaderInfo -import HscTypes +import GHC.Driver.Types import Module import GHC.IfaceToCore ( typecheckIface ) import TcRnMonad ( initIfaceCheck ) -import HscMain +import GHC.Driver.Main import Bag ( unitBag, listToBag, unionManyBags, isEmptyBag ) import BasicTypes @@ -65,7 +65,7 @@ import StringBuffer import UniqFM import UniqDSet import TcBackpack -import Packages +import GHC.Driver.Packages import UniqSet import Util import qualified GHC.LanguageExtensions as LangExt @@ -675,7 +675,7 @@ guessOutputFile = modifySession $ \env -> #if defined(mingw32_HOST_OS) -- we must add the .exe extension unconditionally here, otherwise -- when name has an extension of its own, the .exe extension will - -- not be added by DriverPipeline.exeFileName. See #2248 + -- not be added by GHC.Driver.Pipeline.exeFileName. See #2248 name' <- fmap (<.> "exe") name #else name' <- name @@ -808,7 +808,7 @@ unload hsc_env stable_linkables -- Unload everything *except* 'stable_linkables' - Note that even if an object is stable, we may end up recompiling if the interface is out of date because an *external* interface - has changed. The current code in GhcMake handles this case + has changed. The current code in GHC.Driver.Make handles this case fairly poorly, so be careful. -} diff --git a/compiler/main/DriverMkDepend.hs b/compiler/GHC/Driver/MakeFile.hs index 04b438c018..d1d3b00394 100644 --- a/compiler/main/DriverMkDepend.hs +++ b/compiler/GHC/Driver/MakeFile.hs @@ -8,23 +8,24 @@ -- ----------------------------------------------------------------------------- -module DriverMkDepend ( - doMkDependHS - ) where +module GHC.Driver.MakeFile + ( doMkDependHS + ) +where #include "HsVersions.h" import GhcPrelude import qualified GHC -import GhcMonad -import DynFlags +import GHC.Driver.Monad +import GHC.Driver.Session import Util -import HscTypes +import GHC.Driver.Types import qualified SysTools import Module import Digraph ( SCC(..) ) -import Finder +import GHC.Driver.Finder import Outputable import Panic import SrcLoc diff --git a/compiler/main/GhcMonad.hs b/compiler/GHC/Driver/Monad.hs index 846744c439..3825757ac6 100644 --- a/compiler/main/GhcMonad.hs +++ b/compiler/GHC/Driver/Monad.hs @@ -8,7 +8,7 @@ -- -- ----------------------------------------------------------------------------- -module GhcMonad ( +module GHC.Driver.Monad ( -- * 'Ghc' monad stuff GhcMonad(..), Ghc(..), @@ -26,8 +26,8 @@ module GhcMonad ( import GhcPrelude import MonadUtils -import HscTypes -import DynFlags +import GHC.Driver.Types +import GHC.Driver.Session import Exception import ErrUtils diff --git a/compiler/main/Packages.hs b/compiler/GHC/Driver/Packages.hs index 2817c99a5a..572da5f3d1 100644 --- a/compiler/main/Packages.hs +++ b/compiler/GHC/Driver/Packages.hs @@ -3,7 +3,7 @@ {-# LANGUAGE CPP, ScopedTypeVariables, BangPatterns, FlexibleContexts #-} -- | Package manipulation -module Packages ( +module GHC.Driver.Packages ( module UnitInfo, -- * Reading the package config, and processing cmdline args @@ -70,7 +70,7 @@ import GhcPrelude import GHC.PackageDb import UnitInfo -import DynFlags +import GHC.Driver.Session import Name ( Name, nameModule_maybe ) import UniqFM import UniqDFM diff --git a/compiler/main/Packages.hs-boot b/compiler/GHC/Driver/Packages.hs-boot index 3fd481021d..89fb2a1c18 100644 --- a/compiler/main/Packages.hs-boot +++ b/compiler/GHC/Driver/Packages.hs-boot @@ -1,6 +1,6 @@ -module Packages where +module GHC.Driver.Packages where import GhcPrelude -import {-# SOURCE #-} DynFlags(DynFlags) +import {-# SOURCE #-} GHC.Driver.Session (DynFlags) import {-# SOURCE #-} Module(ComponentId, UnitId, InstalledUnitId) data PackageState data UnitInfoMap diff --git a/compiler/main/DriverPhases.hs b/compiler/GHC/Driver/Phases.hs index 5c88faf895..45cb4656ba 100644 --- a/compiler/main/DriverPhases.hs +++ b/compiler/GHC/Driver/Phases.hs @@ -1,7 +1,6 @@ {-# LANGUAGE CPP #-} ----------------------------------------------------------------------------- --- $Id: DriverPhases.hs,v 1.38 2005/05/17 11:01:59 simonmar Exp $ -- -- GHC Driver -- @@ -9,7 +8,7 @@ -- ----------------------------------------------------------------------------- -module DriverPhases ( +module GHC.Driver.Phases ( HscSource(..), isHsBootOrSig, isHsigFile, hscSourceString, Phase(..), happensBefore, eqPhase, anyHsc, isStopLn, @@ -42,7 +41,7 @@ module DriverPhases ( import GhcPrelude -import {-# SOURCE #-} DynFlags +import {-# SOURCE #-} GHC.Driver.Session import Outputable import GHC.Platform import System.FilePath @@ -187,7 +186,7 @@ eqPhase _ _ = False We want to know which phases will occur before which others. This is used for sanity checking, to ensure that the pipeline will stop at some point (see -DriverPipeline.runPipeline). +GHC.Driver.Pipeline.runPipeline). A < B iff A occurs before B in a normal compilation pipeline. diff --git a/compiler/main/DriverPipeline.hs b/compiler/GHC/Driver/Pipeline.hs index 99a3ae9b70..3c31e34eb8 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/GHC/Driver/Pipeline.hs @@ -10,7 +10,7 @@ -- ----------------------------------------------------------------------------- -module DriverPipeline ( +module GHC.Driver.Pipeline ( -- Run a series of compilation steps in a pipeline, for a -- collection of source files. oneShot, compileFile, @@ -38,19 +38,19 @@ module DriverPipeline ( import GhcPrelude -import PipelineMonad -import Packages +import GHC.Driver.Pipeline.Monad +import GHC.Driver.Packages import HeaderInfo -import DriverPhases +import GHC.Driver.Phases import SysTools import SysTools.ExtraObj -import HscMain -import Finder -import HscTypes hiding ( Hsc ) +import GHC.Driver.Main +import GHC.Driver.Finder +import GHC.Driver.Types hiding ( Hsc ) import Outputable import Module import ErrUtils -import DynFlags +import GHC.Driver.Session import Panic import Util import StringBuffer ( hGetStringBuffer, hPutStringBuffer ) @@ -62,7 +62,7 @@ import MonadUtils import GHC.Platform import TcRnTypes import ToolSettings -import Hooks +import GHC.Driver.Hooks import qualified GHC.LanguageExtensions as LangExt import FileCleanup import Ar @@ -2120,9 +2120,9 @@ enabled in the toolchain: We must enable bigobj output in a few places: - * When merging object files (DriverPipeline.joinObjectFiles) + * When merging object files (GHC.Driver.Pipeline.joinObjectFiles) - * When assembling (DriverPipeline.runPhase (RealPhase As ...)) + * When assembling (GHC.Driver.Pipeline.runPhase (RealPhase As ...)) Unfortunately the big object format is not supported on 32-bit targets so none of this can be used in that case. diff --git a/compiler/main/PipelineMonad.hs b/compiler/GHC/Driver/Pipeline/Monad.hs index a3608ac4cd..5831f923ea 100644 --- a/compiler/main/PipelineMonad.hs +++ b/compiler/GHC/Driver/Pipeline/Monad.hs @@ -3,7 +3,7 @@ -- | The CompPipeline monad and associated ops -- -- Defined in separate module so that it can safely be imported from Hooks -module PipelineMonad ( +module GHC.Driver.Pipeline.Monad ( CompPipeline(..), evalP , PhasePlus(..) , PipeEnv(..), PipeState(..), PipelineOutput(..) @@ -15,9 +15,9 @@ import GhcPrelude import MonadUtils import Outputable -import DynFlags -import DriverPhases -import HscTypes +import GHC.Driver.Session +import GHC.Driver.Phases +import GHC.Driver.Types import Module import FileCleanup (TempFileLifetime) diff --git a/compiler/main/Plugins.hs b/compiler/GHC/Driver/Plugins.hs index cb367b4f67..baa27a0b36 100644 --- a/compiler/main/Plugins.hs +++ b/compiler/GHC/Driver/Plugins.hs @@ -5,7 +5,7 @@ -- several areas of the compiler. See the 'Plugin' type. These plugins -- include type-checker plugins, source plugins, and core-to-core plugins. -module Plugins ( +module GHC.Driver.Plugins ( -- * Plugins Plugin(..) , defaultPlugin @@ -54,10 +54,10 @@ import qualified TcRnTypes import TcRnTypes ( TcGblEnv, IfM, TcM, tcg_rn_decls, tcg_rn_exports ) import TcHoleFitTypes ( HoleFitPluginR ) import GHC.Hs -import DynFlags -import HscTypes -import GhcMonad -import DriverPhases +import GHC.Driver.Session +import GHC.Driver.Types +import GHC.Driver.Monad +import GHC.Driver.Phases import Module ( ModuleName, Module(moduleName)) import Fingerprint import Data.List (sort) @@ -104,7 +104,7 @@ data Plugin = Plugin { , parsedResultAction :: [CommandLineOption] -> ModSummary -> HsParsedModule -> Hsc HsParsedModule -- ^ Modify the module when it is parsed. This is called by - -- HscMain when the parsing is successful. + -- GHC.Driver.Main when the parsing is successful. , renamedResultAction :: [CommandLineOption] -> TcGblEnv -> HsGroup GhcRn -> TcM (TcGblEnv, HsGroup GhcRn) -- ^ Modify each group after it is renamed. This is called after each diff --git a/compiler/main/Plugins.hs-boot b/compiler/GHC/Driver/Plugins.hs-boot index c90c6ebaf7..41a0c115d2 100644 --- a/compiler/main/Plugins.hs-boot +++ b/compiler/GHC/Driver/Plugins.hs-boot @@ -1,6 +1,6 @@ -- The plugins datatype is stored in DynFlags, so it needs to be -- exposed without importing all of its implementation. -module Plugins where +module GHC.Driver.Plugins where import GhcPrelude () diff --git a/compiler/main/DynFlags.hs b/compiler/GHC/Driver/Session.hs index 42205ac0b2..4eb9ab2597 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/GHC/Driver/Session.hs @@ -19,7 +19,7 @@ -- -fno-cse is needed for GLOBAL_VAR's to behave properly {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} -module DynFlags ( +module GHC.Driver.Session ( -- * Dynamic flags and associated configuration types DumpFlag(..), GeneralFlag(..), @@ -252,15 +252,15 @@ import GHC.Platform import GHC.UniqueSubdir (uniqueSubdir) import PlatformConstants import Module -import {-# SOURCE #-} Plugins -import {-# SOURCE #-} Hooks +import {-# SOURCE #-} GHC.Driver.Plugins +import {-# SOURCE #-} GHC.Driver.Hooks import {-# SOURCE #-} PrelNames ( mAIN ) -import {-# SOURCE #-} Packages (PackageState, emptyPackageState, PackageDatabase) -import DriverPhases ( Phase(..), phaseInputExt ) +import {-# SOURCE #-} GHC.Driver.Packages (PackageState, emptyPackageState, PackageDatabase) +import GHC.Driver.Phases ( Phase(..), phaseInputExt ) import Config import CliOption -import CmdLineParser hiding (WarnReason(..)) -import qualified CmdLineParser as Cmd +import GHC.Driver.CmdLine hiding (WarnReason(..)) +import qualified GHC.Driver.CmdLine as Cmd import Constants import GhcNameVersion import Panic @@ -1073,11 +1073,11 @@ data DynFlags = DynFlags { outputHi :: Maybe String, dynLibLoader :: DynLibLoader, - -- | This is set by 'DriverPipeline.runPipeline' based on where + -- | This is set by 'GHC.Driver.Pipeline.runPipeline' based on where -- its output is going. dumpPrefix :: Maybe FilePath, - -- | Override the 'dumpPrefix' set by 'DriverPipeline.runPipeline'. + -- | Override the 'dumpPrefix' set by 'GHC.Driver.Pipeline.runPipeline'. -- Set by @-ddump-file-prefix@ dumpPrefixForce :: Maybe FilePath, @@ -2897,7 +2897,7 @@ safeFlagCheck cmdl dflags = "-fpackage-trust ignored;" ++ " must be specified with a Safe Haskell flag"] - -- Have we inferred Unsafe? See Note [HscMain . Safe Haskell Inference] + -- Have we inferred Unsafe? See Note [GHC.Driver.Main . Safe Haskell Inference] safeFlags = all (\(_,_,t,_) -> not $ t dflags) unsafeFlagsForInfer diff --git a/compiler/main/DynFlags.hs-boot b/compiler/GHC/Driver/Session.hs-boot index 6d471f3970..c61d6b5297 100644 --- a/compiler/main/DynFlags.hs-boot +++ b/compiler/GHC/Driver/Session.hs-boot @@ -1,4 +1,4 @@ -module DynFlags where +module GHC.Driver.Session where import GhcPrelude import GHC.Platform diff --git a/compiler/main/HscTypes.hs b/compiler/GHC/Driver/Types.hs index 25b2f3e172..7fd8fe73c3 100644 --- a/compiler/main/HscTypes.hs +++ b/compiler/GHC/Driver/Types.hs @@ -1,7 +1,7 @@ {- (c) The University of Glasgow, 2006 -\section[HscTypes]{Types for the per-module compiler} +\section[GHC.Driver.Types]{Types for the per-module compiler} -} {-# LANGUAGE CPP, ScopedTypeVariables #-} @@ -16,7 +16,7 @@ {-# LANGUAGE DataKinds #-} -- | Types for the per-module compiler -module HscTypes ( +module GHC.Driver.Types ( -- * compilation state HscEnv(..), hscEPS, FinderCache, FindResult(..), InstalledFindResult(..), @@ -45,7 +45,7 @@ module HscTypes ( SourceModified(..), isTemplateHaskellOrQQNonBoot, -- * Information about the module being compiled - -- (re-exported from DriverPhases) + -- (re-exported from GHC.Driver.Phases) HscSource(..), isHsBootOrSig, isHsigFile, hscSourceString, @@ -187,13 +187,13 @@ import DataCon import PatSyn import PrelNames ( gHC_PRIM, ioTyConName, printName, mkInteractiveModule ) import TysWiredIn -import Packages hiding ( Version(..) ) -import CmdLineParser -import DynFlags +import GHC.Driver.Packages hiding ( Version(..) ) +import GHC.Driver.CmdLine +import GHC.Driver.Session import GHC.Runtime.Linker.Types ( DynLinker, Linkable(..), Unlinked(..), SptEntry(..) ) -import DriverPhases ( Phase, HscSource(..), hscSourceString +import GHC.Driver.Phases ( Phase, HscSource(..), hscSourceString , isHsBootOrSig, isHsigFile ) -import qualified DriverPhases as Phase +import qualified GHC.Driver.Phases as Phase import BasicTypes import GHC.Iface.Syntax import Maybes @@ -304,7 +304,7 @@ runInteractiveHsc hsc_env = runHsc (mkInteractiveHscEnv hsc_env) -- ----------------------------------------------------------------------------- -- Source Errors --- When the compiler (HscMain) discovers errors, it throws an +-- When the compiler (GHC.Driver.Main) discovers errors, it throws an -- exception in the IO monad. mkSrcErr :: ErrorMessages -> SourceError @@ -393,7 +393,7 @@ handleFlagWarnings dflags warns = do printOrThrowWarnings dflags bag -- Given a warn reason, check to see if it's associated -W opt is enabled -shouldPrintWarning :: DynFlags -> CmdLineParser.WarnReason -> Bool +shouldPrintWarning :: DynFlags -> GHC.Driver.CmdLine.WarnReason -> Bool shouldPrintWarning dflags ReasonDeprecatedFlag = wopt Opt_WarnDeprecatedFlags dflags shouldPrintWarning dflags ReasonUnrecognisedFlag @@ -679,7 +679,7 @@ data HomeModInfo -- After a complete compilation ('GHC.load'), all 'hm_linkable' fields -- in the 'HomePackageTable' will be @Just@. -- - -- When re-linking a module ('HscMain.HscNoRecomp'), we construct the + -- When re-linking a module ('GHC.Driver.Main.HscNoRecomp'), we construct the -- 'HomeModInfo' by building a new 'ModDetails' from the old -- 'ModIface' (only). } diff --git a/compiler/GHC/HsToCore.hs b/compiler/GHC/HsToCore.hs index fc290737ca..ec888766a7 100644 --- a/compiler/GHC/HsToCore.hs +++ b/compiler/GHC/HsToCore.hs @@ -21,8 +21,8 @@ module GHC.HsToCore ( import GhcPrelude import GHC.HsToCore.Usage -import DynFlags -import HscTypes +import GHC.Driver.Session +import GHC.Driver.Types import GHC.Hs import TcRnTypes import TcRnMonad ( finalSafeMode, fixSafeInstances ) @@ -70,7 +70,7 @@ import GHC.HsToCore.Docs import Data.List import Data.IORef import Control.Monad( when ) -import Plugins ( LoadedPlugin(..) ) +import GHC.Driver.Plugins ( LoadedPlugin(..) ) {- ************************************************************************ diff --git a/compiler/GHC/HsToCore/Binds.hs b/compiler/GHC/HsToCore/Binds.hs index a6bbe4ca54..124427578d 100644 --- a/compiler/GHC/HsToCore/Binds.hs +++ b/compiler/GHC/HsToCore/Binds.hs @@ -68,7 +68,7 @@ import Maybes import OrdList import Bag import BasicTypes -import DynFlags +import GHC.Driver.Session import FastString import Util import UniqSet( nonDetEltsUniqSet ) diff --git a/compiler/GHC/HsToCore/Coverage.hs b/compiler/GHC/HsToCore/Coverage.hs index ace0b27b4e..a87d46bbcc 100644 --- a/compiler/GHC/HsToCore/Coverage.hs +++ b/compiler/GHC/HsToCore/Coverage.hs @@ -23,7 +23,7 @@ import Type import GHC.Hs import Module import Outputable -import DynFlags +import GHC.Driver.Session import ConLike import Control.Monad import SrcLoc @@ -38,7 +38,7 @@ import Id import VarSet import Data.List import FastString -import HscTypes +import GHC.Driver.Types import TyCon import BasicTypes import MonadUtils diff --git a/compiler/GHC/HsToCore/Expr.hs b/compiler/GHC/HsToCore/Expr.hs index f400a1fdf1..b627d6e841 100644 --- a/compiler/GHC/HsToCore/Expr.hs +++ b/compiler/GHC/HsToCore/Expr.hs @@ -49,7 +49,7 @@ import CoreSyn import CoreUtils import MkCore -import DynFlags +import GHC.Driver.Session import CostCentre import Id import MkId diff --git a/compiler/GHC/HsToCore/Foreign/Call.hs b/compiler/GHC/HsToCore/Foreign/Call.hs index abbc9f3f79..ce39cf4d3c 100644 --- a/compiler/GHC/HsToCore/Foreign/Call.hs +++ b/compiler/GHC/HsToCore/Foreign/Call.hs @@ -45,7 +45,7 @@ import TysWiredIn import BasicTypes import Literal import PrelNames -import DynFlags +import GHC.Driver.Session import Outputable import Util diff --git a/compiler/GHC/HsToCore/Foreign/Decl.hs b/compiler/GHC/HsToCore/Foreign/Decl.hs index de14f6ee12..dc569bdbfa 100644 --- a/compiler/GHC/HsToCore/Foreign/Decl.hs +++ b/compiler/GHC/HsToCore/Foreign/Decl.hs @@ -41,7 +41,7 @@ import TcType import GHC.Cmm.Expr import GHC.Cmm.Utils -import HscTypes +import GHC.Driver.Types import ForeignCall import TysWiredIn import TysPrim @@ -50,11 +50,11 @@ import BasicTypes import SrcLoc import Outputable import FastString -import DynFlags +import GHC.Driver.Session import GHC.Platform import OrdList import Util -import Hooks +import GHC.Driver.Hooks import Encoding import Data.Maybe diff --git a/compiler/GHC/HsToCore/GuardedRHSs.hs b/compiler/GHC/HsToCore/GuardedRHSs.hs index 94821ec68e..37a7cd591b 100644 --- a/compiler/GHC/HsToCore/GuardedRHSs.hs +++ b/compiler/GHC/HsToCore/GuardedRHSs.hs @@ -24,7 +24,7 @@ import CoreSyn import CoreUtils (bindNonRec) import BasicTypes (Origin(FromSource)) -import DynFlags +import GHC.Driver.Session import GHC.HsToCore.PmCheck (needToRunPmCheck, addTyCsDs, addPatTmCs, addScrutTmCs) import GHC.HsToCore.Monad import GHC.HsToCore.Utils diff --git a/compiler/GHC/HsToCore/ListComp.hs b/compiler/GHC/HsToCore/ListComp.hs index a8ed3bbcb3..0411542d78 100644 --- a/compiler/GHC/HsToCore/ListComp.hs +++ b/compiler/GHC/HsToCore/ListComp.hs @@ -26,7 +26,7 @@ import MkCore import GHC.HsToCore.Monad -- the monadery used in the desugarer import GHC.HsToCore.Utils -import DynFlags +import GHC.Driver.Session import CoreUtils import Id import Type diff --git a/compiler/GHC/HsToCore/Match.hs b/compiler/GHC/HsToCore/Match.hs index 16bf73aab8..0542fd5e7e 100644 --- a/compiler/GHC/HsToCore/Match.hs +++ b/compiler/GHC/HsToCore/Match.hs @@ -28,7 +28,7 @@ import GhcPrelude import {-#SOURCE#-} GHC.HsToCore.Expr (dsLExpr, dsSyntaxExpr) import BasicTypes ( Origin(..) ) -import DynFlags +import GHC.Driver.Session import GHC.Hs import TcHsSyn import TcEvidence diff --git a/compiler/GHC/HsToCore/Match/Literal.hs b/compiler/GHC/HsToCore/Match/Literal.hs index 350a5ed8eb..2fdb1a3dd5 100644 --- a/compiler/GHC/HsToCore/Match/Literal.hs +++ b/compiler/GHC/HsToCore/Match/Literal.hs @@ -50,7 +50,7 @@ import SrcLoc import Data.Ratio import Outputable import BasicTypes -import DynFlags +import GHC.Driver.Session import Util import FastString import qualified GHC.LanguageExtensions as LangExt diff --git a/compiler/GHC/HsToCore/Monad.hs b/compiler/GHC/HsToCore/Monad.hs index 4dc7590a47..b13a7f3304 100644 --- a/compiler/GHC/HsToCore/Monad.hs +++ b/compiler/GHC/HsToCore/Monad.hs @@ -64,7 +64,7 @@ import GHC.IfaceToCore import TcMType ( checkForLevPolyX, formatLevPolyErr ) import PrelNames import RdrName -import HscTypes +import GHC.Driver.Types import Bag import BasicTypes ( Origin ) import DataCon @@ -79,7 +79,7 @@ import Type import UniqSupply import Name import NameEnv -import DynFlags +import GHC.Driver.Session import ErrUtils import FastString import UniqFM ( lookupWithDefaultUFM ) diff --git a/compiler/GHC/HsToCore/PmCheck.hs b/compiler/GHC/HsToCore/PmCheck.hs index ce81b8b587..2a7d70abd2 100644 --- a/compiler/GHC/HsToCore/PmCheck.hs +++ b/compiler/GHC/HsToCore/PmCheck.hs @@ -30,7 +30,7 @@ import GHC.HsToCore.PmCheck.Ppr import BasicTypes (Origin, isGenerated) import CoreSyn (CoreExpr, Expr(Var,App)) import FastString (unpackFS, lengthFS) -import DynFlags +import GHC.Driver.Session import GHC.Hs import TcHsSyn import Id diff --git a/compiler/GHC/HsToCore/PmCheck/Oracle.hs b/compiler/GHC/HsToCore/PmCheck/Oracle.hs index ab0f8ccc29..c0722249d8 100644 --- a/compiler/GHC/HsToCore/PmCheck/Oracle.hs +++ b/compiler/GHC/HsToCore/PmCheck/Oracle.hs @@ -29,7 +29,7 @@ import GhcPrelude import GHC.HsToCore.PmCheck.Types -import DynFlags +import GHC.Driver.Session import Outputable import ErrUtils import Util diff --git a/compiler/GHC/HsToCore/Quote.hs b/compiler/GHC/HsToCore/Quote.hs index 292cb4dca0..e9d7a2ca50 100644 --- a/compiler/GHC/HsToCore/Quote.hs +++ b/compiler/GHC/HsToCore/Quote.hs @@ -59,7 +59,7 @@ import Unique import BasicTypes import Outputable import Bag -import DynFlags +import GHC.Driver.Session import FastString import ForeignCall import Util @@ -69,7 +69,7 @@ import TcEvidence import Control.Monad.Trans.Reader import Control.Monad.Trans.Class import Class -import HscTypes ( MonadThings ) +import GHC.Driver.Types ( MonadThings ) import DataCon import Var import GHC.HsToCore.Binds diff --git a/compiler/GHC/HsToCore/Usage.hs b/compiler/GHC/HsToCore/Usage.hs index f771608a94..b83d310e0a 100644 --- a/compiler/GHC/HsToCore/Usage.hs +++ b/compiler/GHC/HsToCore/Usage.hs @@ -13,8 +13,8 @@ module GHC.HsToCore.Usage ( import GhcPrelude -import DynFlags -import HscTypes +import GHC.Driver.Session +import GHC.Driver.Types import TcRnTypes import Name import NameSet @@ -25,8 +25,8 @@ import UniqSet import UniqFM import Fingerprint import Maybes -import Packages -import Finder +import GHC.Driver.Packages +import GHC.Driver.Finder import Control.Monad (filterM) import Data.List diff --git a/compiler/GHC/HsToCore/Utils.hs b/compiler/GHC/HsToCore/Utils.hs index 3c95e55b19..953225e912 100644 --- a/compiler/GHC/HsToCore/Utils.hs +++ b/compiler/GHC/HsToCore/Utils.hs @@ -77,7 +77,7 @@ import Name( isInternalName ) import Outputable import SrcLoc import Util -import DynFlags +import GHC.Driver.Session import FastString import qualified GHC.LanguageExtensions as LangExt diff --git a/compiler/GHC/Iface/Binary.hs b/compiler/GHC/Iface/Binary.hs index af0e9bfac6..c5850f1eaf 100644 --- a/compiler/GHC/Iface/Binary.hs +++ b/compiler/GHC/Iface/Binary.hs @@ -38,10 +38,10 @@ import GhcPrelude import TcRnMonad import PrelInfo ( isKnownKeyName, lookupKnownKeyName ) import GHC.Iface.Env -import HscTypes +import GHC.Driver.Types import Module import Name -import DynFlags +import GHC.Driver.Session import UniqFM import UniqSupply import Panic diff --git a/compiler/GHC/Iface/Env.hs b/compiler/GHC/Iface/Env.hs index fcb1e2dcfb..687989f0a6 100644 --- a/compiler/GHC/Iface/Env.hs +++ b/compiler/GHC/Iface/Env.hs @@ -25,7 +25,7 @@ module GHC.Iface.Env ( import GhcPrelude import TcRnMonad -import HscTypes +import GHC.Driver.Types import Type import Var import Name diff --git a/compiler/GHC/Iface/Ext/Ast.hs b/compiler/GHC/Iface/Ext/Ast.hs index 690aa323c9..edeeaf651e 100644 --- a/compiler/GHC/Iface/Ext/Ast.hs +++ b/compiler/GHC/Iface/Ext/Ast.hs @@ -28,7 +28,7 @@ import ConLike ( conLikeName ) import GHC.HsToCore ( deSugarExpr ) import FieldLabel import GHC.Hs -import HscTypes +import GHC.Driver.Types import Module ( ModuleName, ml_hs_file ) import MonadUtils ( concatMapM, liftIO ) import Name ( Name, nameSrcSpan, setNameLoc ) diff --git a/compiler/GHC/Iface/Ext/Utils.hs b/compiler/GHC/Iface/Ext/Utils.hs index eba14f190a..007634bae6 100644 --- a/compiler/GHC/Iface/Ext/Utils.hs +++ b/compiler/GHC/Iface/Ext/Utils.hs @@ -7,7 +7,7 @@ module GHC.Iface.Ext.Utils where import GhcPrelude import CoreMap -import DynFlags ( DynFlags ) +import GHC.Driver.Session ( DynFlags ) import FastString ( FastString, mkFastString ) import GHC.Iface.Type import Name hiding (varName) diff --git a/compiler/GHC/Iface/Load.hs b/compiler/GHC/Iface/Load.hs index c11d4b3e4f..cde0e8c9e2 100644 --- a/compiler/GHC/Iface/Load.hs +++ b/compiler/GHC/Iface/Load.hs @@ -40,10 +40,10 @@ import {-# SOURCE #-} GHC.IfaceToCore ( tcIfaceDecl, tcIfaceRules, tcIfaceInst, tcIfaceFamInst , tcIfaceAnnotations, tcIfaceCompleteSigs ) -import DynFlags +import GHC.Driver.Session import GHC.Iface.Syntax import GHC.Iface.Env -import HscTypes +import GHC.Driver.Types import BasicTypes hiding (SuccessFlag(..)) import TcRnMonad @@ -65,7 +65,7 @@ import Avail import Module import Maybes import ErrUtils -import Finder +import GHC.Driver.Finder import UniqFM import SrcLoc import Outputable @@ -74,11 +74,11 @@ import Panic import Util import FastString import Fingerprint -import Hooks +import GHC.Driver.Hooks import FieldLabel import GHC.Iface.Rename import UniqDSet -import Plugins +import GHC.Driver.Plugins import Control.Monad import Control.Exception @@ -863,7 +863,7 @@ Note [Home module load error] If the sought-for interface is in the current package (as determined by -package-name flag) then it jolly well should already be in the HPT because we process home-package modules in dependency order. (Except -in one-shot mode; see notes with hsc_HPT decl in HscTypes). +in one-shot mode; see notes with hsc_HPT decl in GHC.Driver.Types). It is possible (though hard) to get this error through user behaviour. * Suppose package P (modules P1, P2) depends on package Q (modules Q1, diff --git a/compiler/GHC/Iface/Load.hs-boot b/compiler/GHC/Iface/Load.hs-boot index e3dce1d68f..a2af2a1a9a 100644 --- a/compiler/GHC/Iface/Load.hs-boot +++ b/compiler/GHC/Iface/Load.hs-boot @@ -2,7 +2,7 @@ module GHC.Iface.Load where import Module (Module) import TcRnMonad (IfM) -import HscTypes (ModIface) +import GHC.Driver.Types (ModIface) import Outputable (SDoc) loadSysInterface :: SDoc -> Module -> IfM lcl ModIface diff --git a/compiler/GHC/Iface/Rename.hs b/compiler/GHC/Iface/Rename.hs index 693f9068c4..3cadf15e80 100644 --- a/compiler/GHC/Iface/Rename.hs +++ b/compiler/GHC/Iface/Rename.hs @@ -21,7 +21,7 @@ import GhcPrelude import SrcLoc import Outputable -import HscTypes +import GHC.Driver.Types import Module import UniqFM import Avail @@ -38,13 +38,13 @@ import BasicTypes -- a bit vexing import {-# SOURCE #-} GHC.Iface.Load -import DynFlags +import GHC.Driver.Session import qualified Data.Traversable as T import Bag import Data.IORef -import NameShape +import GHC.Types.Name.Shape import GHC.Iface.Env tcRnMsgMaybe :: IO (Either ErrorMessages a) -> TcM a diff --git a/compiler/GHC/Iface/Syntax.hs b/compiler/GHC/Iface/Syntax.hs index c831d09c7f..cea861de27 100644 --- a/compiler/GHC/Iface/Syntax.hs +++ b/compiler/GHC/Iface/Syntax.hs @@ -403,10 +403,10 @@ ifaceDeclImplicitBndrs :: IfaceDecl -> [OccName] -- *Excludes* the 'main' name, but *includes* the implicitly-bound names -- Deeply revolting, because it has to predict what gets bound, -- especially the question of whether there's a wrapper for a datacon --- See Note [Implicit TyThings] in HscTypes +-- See Note [Implicit TyThings] in GHC.Driver.Types -- N.B. the set of names returned here *must* match the set of --- TyThings returned by HscTypes.implicitTyThings, in the sense that +-- TyThings returned by GHC.Driver.Types.implicitTyThings, in the sense that -- TyThing.getOccName should define a bijection between the two lists. -- This invariant is used in GHC.Iface.Load.loadDecl (see note [Tricky iface loop]) -- The order of the list does not matter. @@ -1741,7 +1741,7 @@ not happen. Here's the one that bit me: data DynFlags = DF ... PackageState ... module Packages where - import DynFlags + import GHC.Driver.Session data PackageState = PS ... lookupModule (df :: DynFlags) = case df of diff --git a/compiler/GHC/Iface/Tidy.hs b/compiler/GHC/Iface/Tidy.hs index 3d08b139b5..49a5a29856 100644 --- a/compiler/GHC/Iface/Tidy.hs +++ b/compiler/GHC/Iface/Tidy.hs @@ -17,7 +17,7 @@ module GHC.Iface.Tidy ( import GhcPrelude import TcRnTypes -import DynFlags +import GHC.Driver.Session import CoreSyn import CoreUnfold import CoreFVs @@ -53,7 +53,7 @@ import DataCon import TyCon import Class import Module -import HscTypes +import GHC.Driver.Types import Maybes import UniqSupply import Outputable diff --git a/compiler/GHC/Iface/Utils.hs b/compiler/GHC/Iface/Utils.hs index bf221bd88c..83f46bd774 100644 --- a/compiler/GHC/Iface/Utils.hs +++ b/compiler/GHC/Iface/Utils.hs @@ -83,9 +83,9 @@ import InstEnv import FamInstEnv import TcRnMonad import GHC.Hs -import HscTypes -import Finder -import DynFlags +import GHC.Driver.Types +import GHC.Driver.Finder +import GHC.Driver.Session import VarEnv import Var import Name @@ -108,7 +108,7 @@ import Binary import Fingerprint import Exception import UniqSet -import Packages +import GHC.Driver.Packages import GHC.HsToCore.Docs import Control.Monad @@ -120,7 +120,7 @@ import Data.Ord import Data.IORef import System.Directory import System.FilePath -import Plugins ( PluginRecompile(..), PluginWithArgs(..), LoadedPlugin(..), +import GHC.Driver.Plugins ( PluginRecompile(..), PluginWithArgs(..), LoadedPlugin(..), pluginRecompile', plugins ) --Qualified import so we can define a Semigroup instance diff --git a/compiler/GHC/IfaceToCore.hs b/compiler/GHC/IfaceToCore.hs index aa74a16284..589843e404 100644 --- a/compiler/GHC/IfaceToCore.hs +++ b/compiler/GHC/IfaceToCore.hs @@ -38,7 +38,7 @@ import Coercion import CoAxiom import TyCoRep -- needs to build types & coercions in a knot import TyCoSubst ( substTyCoVars ) -import HscTypes +import GHC.Driver.Types import Annotations import InstEnv import FamInstEnv @@ -70,7 +70,7 @@ import UniqSupply import Outputable import Maybes import SrcLoc -import DynFlags +import GHC.Driver.Session import Util import FastString import BasicTypes hiding ( SuccessFlag(..) ) @@ -128,14 +128,14 @@ a Name for another entity defined in A.hi. How do we get the internal TyCons to MATCH the ones that we just constructed during typechecking: the knot is thus tied through if_rec_types. - 2) retypecheckLoop in GhcMake: We are retypechecking a + 2) retypecheckLoop in GHC.Driver.Make: We are retypechecking a mutually recursive cluster of hi files, in order to ensure that all of the references refer to each other correctly. In this case, the knot is tied through the HPT passed in, which contains all of the interfaces we are in the process of typechecking. - 3) genModDetails in HscMain: We are typechecking an + 3) genModDetails in GHC.Driver.Main: We are typechecking an old interface to generate the ModDetails. In this case, we do the same thing as (2) and pass in an HPT with the HomeModInfo being generated to tie knots. diff --git a/compiler/GHC/IfaceToCore.hs-boot b/compiler/GHC/IfaceToCore.hs-boot index 4a888f51f7..521a32d93f 100644 --- a/compiler/GHC/IfaceToCore.hs-boot +++ b/compiler/GHC/IfaceToCore.hs-boot @@ -9,7 +9,7 @@ import TcRnTypes ( IfL ) import InstEnv ( ClsInst ) import FamInstEnv ( FamInst ) import CoreSyn ( CoreRule ) -import HscTypes ( CompleteMatch ) +import GHC.Driver.Types ( CompleteMatch ) import Annotations ( Annotation ) tcIfaceDecl :: Bool -> IfaceDecl -> IfL TyThing diff --git a/compiler/GHC/Llvm/Types.hs b/compiler/GHC/Llvm/Types.hs index 61c2b2cb86..f8ca0c826c 100644 --- a/compiler/GHC/Llvm/Types.hs +++ b/compiler/GHC/Llvm/Types.hs @@ -14,7 +14,7 @@ import Data.Char import Data.Int import Numeric -import DynFlags +import GHC.Driver.Session import FastString import Outputable import Unique diff --git a/compiler/main/GhcPlugins.hs b/compiler/GHC/Plugins.hs index 63c52d8e20..6b3115bbcc 100644 --- a/compiler/main/GhcPlugins.hs +++ b/compiler/GHC/Plugins.hs @@ -3,19 +3,19 @@ -- | This module is not used by GHC itself. Rather, it exports all of -- the functions and types you are likely to need when writing a -- plugin for GHC. So authors of plugins can probably get away simply --- with saying "import GhcPlugins". +-- with saying "import GHC.Plugins". -- -- Particularly interesting modules for plugin writers include -- "CoreSyn" and "CoreMonad". -module GhcPlugins( - module Plugins, +module GHC.Plugins( + module GHC.Driver.Plugins, module RdrName, module OccName, module Name, module Var, module Id, module IdInfo, module CoreMonad, module CoreSyn, module Literal, module DataCon, module CoreUtils, module MkCore, module CoreFVs, module CoreSubst, module Rules, module Annotations, - module DynFlags, module Packages, + module GHC.Driver.Session, module GHC.Driver.Packages, module Module, module Type, module TyCon, module Coercion, - module TysWiredIn, module HscTypes, module BasicTypes, + module TysWiredIn, module GHC.Driver.Types, module BasicTypes, module VarSet, module VarEnv, module NameSet, module NameEnv, module UniqSet, module UniqFM, module FiniteMap, module Util, module GHC.Serialized, module SrcLoc, module Outputable, @@ -26,7 +26,7 @@ module GhcPlugins( ) where -- Plugin stuff itself -import Plugins +import GHC.Driver.Plugins -- Variable naming import RdrName @@ -52,8 +52,8 @@ import Rules import Annotations -- Pipeline-related stuff -import DynFlags -import Packages +import GHC.Driver.Session +import GHC.Driver.Packages -- Important GHC types import Module @@ -63,7 +63,7 @@ import Coercion hiding {- conflict with CoreSubst -} ( substCo ) import TyCon import TysWiredIn -import HscTypes +import GHC.Driver.Types import BasicTypes hiding ( Version {- conflicts with Packages.Version -} ) -- Collections and maps diff --git a/compiler/GHC/Rename/Binds.hs b/compiler/GHC/Rename/Binds.hs index 888b8ce62d..a9a3653e0d 100644 --- a/compiler/GHC/Rename/Binds.hs +++ b/compiler/GHC/Rename/Binds.hs @@ -44,7 +44,7 @@ import GHC.Rename.Utils ( HsDocContext(..), mapFvRn, extendTyVarEnvFVRn , checkDupRdrNames, warnUnusedLocalBinds , checkUnusedRecordWildcard , checkDupAndShadowedNames, bindLocalNamesFV ) -import DynFlags +import GHC.Driver.Session import Module import Name import NameEnv diff --git a/compiler/GHC/Rename/Env.hs b/compiler/GHC/Rename/Env.hs index d300761a68..8e24004653 100644 --- a/compiler/GHC/Rename/Env.hs +++ b/compiler/GHC/Rename/Env.hs @@ -50,7 +50,7 @@ import GHC.Iface.Load ( loadInterfaceForName, loadSrcInterface_maybe ) import GHC.Iface.Env import GHC.Hs import RdrName -import HscTypes +import GHC.Driver.Types import TcEnv import TcRnMonad import RdrHsSyn ( filterCTuple, setRdrNameSpace ) @@ -71,7 +71,7 @@ import Outputable import UniqSet ( uniqSetAny ) import Util import Maybes -import DynFlags +import GHC.Driver.Session import FastString import Control.Monad import ListSetOps ( minusList ) diff --git a/compiler/GHC/Rename/Expr.hs b/compiler/GHC/Rename/Expr.hs index 70b466ef2b..baadf419ad 100644 --- a/compiler/GHC/Rename/Expr.hs +++ b/compiler/GHC/Rename/Expr.hs @@ -44,7 +44,7 @@ import GHC.Rename.Unbound ( reportUnboundName ) import GHC.Rename.Splice ( rnBracket, rnSpliceExpr, checkThLocalName ) import GHC.Rename.Types import GHC.Rename.Pat -import DynFlags +import GHC.Driver.Session import PrelNames import BasicTypes diff --git a/compiler/GHC/Rename/Fixity.hs b/compiler/GHC/Rename/Fixity.hs index 74b886f49c..4c55bb3e53 100644 --- a/compiler/GHC/Rename/Fixity.hs +++ b/compiler/GHC/Rename/Fixity.hs @@ -21,7 +21,7 @@ import GhcPrelude import GHC.Iface.Load import GHC.Hs import RdrName -import HscTypes +import GHC.Driver.Types import TcRnMonad import Name import NameEnv diff --git a/compiler/GHC/Rename/Names.hs b/compiler/GHC/Rename/Names.hs index b666b89875..48208dba46 100644 --- a/compiler/GHC/Rename/Names.hs +++ b/compiler/GHC/Rename/Names.hs @@ -34,7 +34,7 @@ module GHC.Rename.Names ( import GhcPrelude -import DynFlags +import GHC.Driver.Session import TyCoPpr import GHC.Hs import TcEnv @@ -50,7 +50,7 @@ import NameEnv import NameSet import Avail import FieldLabel -import HscTypes +import GHC.Driver.Types import RdrName import RdrHsSyn ( setRdrNameSpace ) import Outputable @@ -86,7 +86,7 @@ import System.IO Note [Tracking Trust Transitively] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ When we import a package as well as checking that the direct imports are safe -according to the rules outlined in the Note [HscMain . Safe Haskell Trust Check] +according to the rules outlined in the Note [Safe Haskell Trust Check] in GHC.Driver.Main we must also check that these rules hold transitively for all dependent modules and packages. Doing this without caching any trust information would be very slow as we would need to touch all packages and interface files a module depends @@ -111,7 +111,7 @@ the plusImportAvails function that is a union operation for the ImportAvails type. This gives us in an ImportAvails structure all packages required to be trusted for the module we are currently compiling. Checking that these packages are still trusted (and that direct imports are trusted) is done in -HscMain.checkSafeImports. +GHC.Driver.Main.checkSafeImports. See the note below, [Trust Own Package] for a corner case in this method and how its handled. @@ -543,7 +543,7 @@ created by its bindings. Note [Top-level Names in Template Haskell decl quotes] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -See also: Note [Interactively-bound Ids in GHCi] in HscTypes +See also: Note [Interactively-bound Ids in GHCi] in GHC.Driver.Types Note [Looking up Exact RdrNames] in GHC.Rename.Env Consider a Template Haskell declaration quotation like this: diff --git a/compiler/GHC/Rename/Source.hs b/compiler/GHC/Rename/Source.hs index 934c346971..9bb577f48b 100644 --- a/compiler/GHC/Rename/Source.hs +++ b/compiler/GHC/Rename/Source.hs @@ -43,7 +43,7 @@ import TcRnMonad import ForeignCall ( CCallTarget(..) ) import Module -import HscTypes ( Warnings(..), plusWarns ) +import GHC.Driver.Types ( Warnings(..), plusWarns ) import PrelNames ( applicativeClassName, pureAName, thenAName , monadClassName, returnMName, thenMName , semigroupClassName, sappendName @@ -58,9 +58,9 @@ import Bag import BasicTypes ( pprRuleName, TypeOrKind(..) ) import FastString import SrcLoc -import DynFlags +import GHC.Driver.Session import Util ( debugIsOn, filterOut, lengthExceeds, partitionWith ) -import HscTypes ( HscEnv, hsc_dflags ) +import GHC.Driver.Types ( HscEnv, hsc_dflags ) import ListSetOps ( findDupsEq, removeDups, equivClasses ) import Digraph ( SCC, flattenSCC, flattenSCCs, Node(..) , stronglyConnCompFromEdgedVerticesUniq ) diff --git a/compiler/GHC/Rename/Splice.hs b/compiler/GHC/Rename/Splice.hs index 9a60a071c5..12496a9fb8 100644 --- a/compiler/GHC/Rename/Splice.hs +++ b/compiler/GHC/Rename/Splice.hs @@ -40,11 +40,11 @@ import {-# SOURCE #-} GHC.Rename.Expr ( rnLExpr ) import TcEnv ( checkWellStaged ) import THNames ( liftName ) -import DynFlags +import GHC.Driver.Session import FastString import ErrUtils ( dumpIfSet_dyn_printer, DumpFormat (..) ) import TcEnv ( tcMetaTy ) -import Hooks +import GHC.Driver.Hooks import THNames ( quoteExpName, quotePatName, quoteDecName, quoteTypeName , decsQTyConName, expQTyConName, patQTyConName, typeQTyConName, ) diff --git a/compiler/GHC/Rename/Types.hs b/compiler/GHC/Rename/Types.hs index 05df4865ec..ed65453c64 100644 --- a/compiler/GHC/Rename/Types.hs +++ b/compiler/GHC/Rename/Types.hs @@ -36,7 +36,7 @@ import GhcPrelude import {-# SOURCE #-} GHC.Rename.Splice( rnSpliceType ) -import DynFlags +import GHC.Driver.Session import GHC.Hs import GHC.Rename.Doc ( rnLHsDoc, rnMbLHsDoc ) import GHC.Rename.Env diff --git a/compiler/GHC/Rename/Unbound.hs b/compiler/GHC/Rename/Unbound.hs index f8b33aa748..1e494331e4 100644 --- a/compiler/GHC/Rename/Unbound.hs +++ b/compiler/GHC/Rename/Unbound.hs @@ -20,7 +20,7 @@ where import GhcPrelude import RdrName -import HscTypes +import GHC.Driver.Types import TcRnMonad import Name import Module @@ -29,7 +29,7 @@ import Outputable import PrelNames ( mkUnboundName, isUnboundName, getUnique) import Util import Maybes -import DynFlags +import GHC.Driver.Session import FastString import Data.List import Data.Function ( on ) diff --git a/compiler/GHC/Rename/Utils.hs b/compiler/GHC/Rename/Utils.hs index 29705c56f0..11cbb745bc 100644 --- a/compiler/GHC/Rename/Utils.hs +++ b/compiler/GHC/Rename/Utils.hs @@ -37,7 +37,7 @@ import GhcPrelude import GHC.Hs import RdrName -import HscTypes +import GHC.Driver.Types import TcEnv import TcRnMonad import Name @@ -49,7 +49,7 @@ import Outputable import Util import BasicTypes ( TopLevelFlag(..) ) import ListSetOps ( removeDups ) -import DynFlags +import GHC.Driver.Session import FastString import Control.Monad import Data.List diff --git a/compiler/GHC/Runtime/Debugger.hs b/compiler/GHC/Runtime/Debugger.hs index 9443ff9421..177a83ea8b 100644 --- a/compiler/GHC/Runtime/Debugger.hs +++ b/compiler/GHC/Runtime/Debugger.hs @@ -21,8 +21,8 @@ import GHC.Runtime.Heap.Inspect import GHC.Runtime.Interpreter import GHCi.RemoteTypes -import GhcMonad -import HscTypes +import GHC.Driver.Monad +import GHC.Driver.Types import Id import GHC.Iface.Syntax ( showToHeader ) import GHC.Iface.Env ( newInteractiveBinder ) @@ -36,7 +36,7 @@ import Outputable import PprTyThing import ErrUtils import MonadUtils -import DynFlags +import GHC.Driver.Session import Exception import Control.Monad diff --git a/compiler/GHC/Runtime/Eval.hs b/compiler/GHC/Runtime/Eval.hs index 666b80cc88..c960b1c8c6 100644 --- a/compiler/GHC/Runtime/Eval.hs +++ b/compiler/GHC/Runtime/Eval.hs @@ -53,10 +53,10 @@ import GHC.Runtime.Eval.Types import GHC.Runtime.Interpreter as GHCi import GHCi.Message import GHCi.RemoteTypes -import GhcMonad -import HscMain +import GHC.Driver.Monad +import GHC.Driver.Main import GHC.Hs -import HscTypes +import GHC.Driver.Types import InstEnv import GHC.Iface.Env ( newInteractiveBinder ) import FamInstEnv ( FamInst ) @@ -77,7 +77,7 @@ import RdrName import VarEnv import GHC.ByteCode.Types import GHC.Runtime.Linker as Linker -import DynFlags +import GHC.Driver.Session import Unique import UniqSupply import MonadUtils diff --git a/compiler/GHC/Runtime/Heap/Inspect.hs b/compiler/GHC/Runtime/Heap/Inspect.hs index de6f9a7af3..7842afcc5d 100644 --- a/compiler/GHC/Runtime/Heap/Inspect.hs +++ b/compiler/GHC/Runtime/Heap/Inspect.hs @@ -29,7 +29,7 @@ import GhcPrelude import GHC.Runtime.Interpreter as GHCi import GHCi.RemoteTypes -import HscTypes +import GHC.Driver.Types import DataCon import Type @@ -54,7 +54,7 @@ import BasicTypes ( Boxity(..) ) import TysPrim import PrelNames import TysWiredIn -import DynFlags +import GHC.Driver.Session import Outputable as Ppr import GHC.Char import GHC.Exts.Heap diff --git a/compiler/GHC/Runtime/Heap/Layout.hs b/compiler/GHC/Runtime/Heap/Layout.hs index b7899ecc1b..8ef91ae741 100644 --- a/compiler/GHC/Runtime/Heap/Layout.hs +++ b/compiler/GHC/Runtime/Heap/Layout.hs @@ -47,7 +47,7 @@ module GHC.Runtime.Heap.Layout ( import GhcPrelude import BasicTypes( ConTagZ ) -import DynFlags +import GHC.Driver.Session import Outputable import GHC.Platform import FastString diff --git a/compiler/GHC/Runtime/Interpreter.hs b/compiler/GHC/Runtime/Interpreter.hs index 9eadacca1c..8524e92cdc 100644 --- a/compiler/GHC/Runtime/Interpreter.hs +++ b/compiler/GHC/Runtime/Interpreter.hs @@ -58,17 +58,17 @@ import GHCi.RemoteTypes import GHCi.ResolvedBCO import GHCi.BreakArray (BreakArray) import Fingerprint -import HscTypes +import GHC.Driver.Types import UniqFM import Panic -import DynFlags +import GHC.Driver.Session import ErrUtils import Outputable import Exception import BasicTypes import FastString import Util -import Hooks +import GHC.Driver.Hooks import Control.Concurrent import Control.Monad diff --git a/compiler/GHC/Runtime/Linker.hs b/compiler/GHC/Runtime/Linker.hs index fb409bd75b..3dcdce34d1 100644 --- a/compiler/GHC/Runtime/Linker.hs +++ b/compiler/GHC/Runtime/Linker.hs @@ -38,16 +38,16 @@ import GHC.ByteCode.Linker import GHC.ByteCode.Asm import GHC.ByteCode.Types import TcRnMonad -import Packages -import DriverPhases -import Finder -import HscTypes +import GHC.Driver.Packages as Packages +import GHC.Driver.Phases +import GHC.Driver.Finder +import GHC.Driver.Types import Name import NameEnv import Module import ListSetOps import GHC.Runtime.Linker.Types (DynLinker(..), LinkerUnitId, PersistentLinkerState(..)) -import DynFlags +import GHC.Driver.Session import BasicTypes import Outputable import Panic diff --git a/compiler/GHC/Runtime/Loader.hs b/compiler/GHC/Runtime/Loader.hs index 0156b16044..15d0b7d5dc 100644 --- a/compiler/GHC/Runtime/Loader.hs +++ b/compiler/GHC/Runtime/Loader.hs @@ -21,12 +21,12 @@ module GHC.Runtime.Loader ( ) where import GhcPrelude -import DynFlags +import GHC.Driver.Session import GHC.Runtime.Linker ( linkModule, getHValue ) import GHC.Runtime.Interpreter ( wormhole ) import SrcLoc ( noSrcSpan ) -import Finder ( findPluginModule, cannotFindModule ) +import GHC.Driver.Finder ( findPluginModule, cannotFindModule ) import TcRnMonad ( initTcInteractive, initIfaceTcRn ) import GHC.Iface.Load ( loadPluginInterface ) import RdrName ( RdrName, ImportSpec(..), ImpDeclSpec(..) @@ -34,10 +34,10 @@ import RdrName ( RdrName, ImportSpec(..), ImpDeclSpec(..) , gre_name, mkRdrQual ) import OccName ( OccName, mkVarOcc ) import GHC.Rename.Names ( gresFromAvails ) -import Plugins +import GHC.Driver.Plugins import PrelNames ( pluginTyConName, frontendPluginTyConName ) -import HscTypes +import GHC.Driver.Types import GHCi.RemoteTypes ( HValue ) import Type ( Type, eqType, mkTyConTy ) import TyCoPpr ( pprTyThingCategory ) @@ -50,7 +50,7 @@ import FastString import ErrUtils import Outputable import Exception -import Hooks +import GHC.Driver.Hooks import Control.Monad ( when, unless ) import Data.Maybe ( mapMaybe ) diff --git a/compiler/GHC/Stg/Lift.hs b/compiler/GHC/Stg/Lift.hs index 0f1a4ccbcb..a0223707d7 100644 --- a/compiler/GHC/Stg/Lift.hs +++ b/compiler/GHC/Stg/Lift.hs @@ -20,7 +20,7 @@ where import GhcPrelude import BasicTypes -import DynFlags +import GHC.Driver.Session import Id import GHC.Stg.FVs ( annBindingFreeVars ) import GHC.Stg.Lift.Analysis diff --git a/compiler/GHC/Stg/Lift/Analysis.hs b/compiler/GHC/Stg/Lift/Analysis.hs index 881d0340a5..b85c460f10 100644 --- a/compiler/GHC/Stg/Lift/Analysis.hs +++ b/compiler/GHC/Stg/Lift/Analysis.hs @@ -24,7 +24,7 @@ import GhcPrelude import BasicTypes import Demand -import DynFlags +import GHC.Driver.Session import Id import GHC.Runtime.Heap.Layout ( WordOff ) import GHC.Stg.Syntax diff --git a/compiler/GHC/Stg/Lift/Monad.hs b/compiler/GHC/Stg/Lift/Monad.hs index 5dd7ab8d65..8cc84172d2 100644 --- a/compiler/GHC/Stg/Lift/Monad.hs +++ b/compiler/GHC/Stg/Lift/Monad.hs @@ -26,7 +26,7 @@ import GhcPrelude import BasicTypes import CostCentre ( isCurrentCCS, dontCareCCS ) -import DynFlags +import GHC.Driver.Session import FastString import Id import Name diff --git a/compiler/GHC/Stg/Lint.hs b/compiler/GHC/Stg/Lint.hs index d2a0b8980e..48d77d0903 100644 --- a/compiler/GHC/Stg/Lint.hs +++ b/compiler/GHC/Stg/Lint.hs @@ -41,7 +41,7 @@ import GhcPrelude import GHC.Stg.Syntax -import DynFlags +import GHC.Driver.Session import Bag ( Bag, emptyBag, isEmptyBag, snocBag, bagToList ) import BasicTypes ( TopLevelFlag(..), isTopLevel ) import CostCentre ( isCurrentCCS ) diff --git a/compiler/GHC/Stg/Pipeline.hs b/compiler/GHC/Stg/Pipeline.hs index 4b6a36536f..457466291d 100644 --- a/compiler/GHC/Stg/Pipeline.hs +++ b/compiler/GHC/Stg/Pipeline.hs @@ -25,7 +25,7 @@ import GHC.Stg.CSE ( stgCse ) import GHC.Stg.Lift ( stgLiftLams ) import Module ( Module ) -import DynFlags +import GHC.Driver.Session import ErrUtils import UniqSupply import Outputable diff --git a/compiler/GHC/Stg/Syntax.hs b/compiler/GHC/Stg/Syntax.hs index 5f52784cb8..eee0e6c6b2 100644 --- a/compiler/GHC/Stg/Syntax.hs +++ b/compiler/GHC/Stg/Syntax.hs @@ -69,14 +69,14 @@ import Data.ByteString ( ByteString ) import Data.Data ( Data ) import Data.List ( intersperse ) import DataCon -import DynFlags +import GHC.Driver.Session import ForeignCall ( ForeignCall ) import Id import VarSet import Literal ( Literal, literalType ) import Module ( Module ) import Outputable -import Packages ( isDllName ) +import GHC.Driver.Packages ( isDllName ) import GHC.Platform import PprCore ( {- instances -} ) import PrimOp ( PrimOp, PrimCall ) diff --git a/compiler/GHC/StgToCmm.hs b/compiler/GHC/StgToCmm.hs index d83e8fbc7b..e5aaf7f5b6 100644 --- a/compiler/GHC/StgToCmm.hs +++ b/compiler/GHC/StgToCmm.hs @@ -30,10 +30,10 @@ import GHC.Cmm import GHC.Cmm.CLabel import GHC.Stg.Syntax -import DynFlags +import GHC.Driver.Session import ErrUtils -import HscTypes +import GHC.Driver.Types import CostCentre import Id import IdInfo diff --git a/compiler/GHC/StgToCmm/ArgRep.hs b/compiler/GHC/StgToCmm/ArgRep.hs index 436b37fced..bd9abbfdea 100644 --- a/compiler/GHC/StgToCmm/ArgRep.hs +++ b/compiler/GHC/StgToCmm/ArgRep.hs @@ -24,7 +24,7 @@ import Id ( Id ) import TyCon ( PrimRep(..), primElemRepSizeB ) import BasicTypes ( RepArity ) import Constants ( wORD64_SIZE ) -import DynFlags +import GHC.Driver.Session import Outputable import FastString diff --git a/compiler/GHC/StgToCmm/Bind.hs b/compiler/GHC/StgToCmm/Bind.hs index 089fec789c..eb0d01ba62 100644 --- a/compiler/GHC/StgToCmm/Bind.hs +++ b/compiler/GHC/StgToCmm/Bind.hs @@ -48,7 +48,7 @@ import VarSet import BasicTypes import Outputable import FastString -import DynFlags +import GHC.Driver.Session import Control.Monad diff --git a/compiler/GHC/StgToCmm/CgUtils.hs b/compiler/GHC/StgToCmm/CgUtils.hs index 58c46f8fa2..095e9c37df 100644 --- a/compiler/GHC/StgToCmm/CgUtils.hs +++ b/compiler/GHC/StgToCmm/CgUtils.hs @@ -24,7 +24,7 @@ import GHC.Cmm.Dataflow.Block import GHC.Cmm.Dataflow.Graph import GHC.Cmm.Utils import GHC.Cmm.CLabel -import DynFlags +import GHC.Driver.Session import Outputable -- ----------------------------------------------------------------------------- diff --git a/compiler/GHC/StgToCmm/Closure.hs b/compiler/GHC/StgToCmm/Closure.hs index b171e7a1fb..d42a7f4764 100644 --- a/compiler/GHC/StgToCmm/Closure.hs +++ b/compiler/GHC/StgToCmm/Closure.hs @@ -85,7 +85,7 @@ import TyCon import GHC.Types.RepType import BasicTypes import Outputable -import DynFlags +import GHC.Driver.Session import Util import Data.Coerce (coerce) diff --git a/compiler/GHC/StgToCmm/DataCon.hs b/compiler/GHC/StgToCmm/DataCon.hs index eb7f9223d7..2f7e350d83 100644 --- a/compiler/GHC/StgToCmm/DataCon.hs +++ b/compiler/GHC/StgToCmm/DataCon.hs @@ -37,7 +37,7 @@ import GHC.Runtime.Heap.Layout import CostCentre import Module import DataCon -import DynFlags +import GHC.Driver.Session import FastString import Id import GHC.Types.RepType (countConRepArgs) diff --git a/compiler/GHC/StgToCmm/Env.hs b/compiler/GHC/StgToCmm/Env.hs index b2c1371840..a0c49e69ee 100644 --- a/compiler/GHC/StgToCmm/Env.hs +++ b/compiler/GHC/StgToCmm/Env.hs @@ -36,7 +36,7 @@ import GHC.Cmm.CLabel import GHC.Cmm.BlockId import GHC.Cmm.Expr import GHC.Cmm.Utils -import DynFlags +import GHC.Driver.Session import Id import GHC.Cmm.Graph import Name diff --git a/compiler/GHC/StgToCmm/Expr.hs b/compiler/GHC/StgToCmm/Expr.hs index 95c8f7defb..589cb770d6 100644 --- a/compiler/GHC/StgToCmm/Expr.hs +++ b/compiler/GHC/StgToCmm/Expr.hs @@ -38,7 +38,7 @@ import GHC.Cmm hiding ( succ ) import GHC.Cmm.Info import CoreSyn import DataCon -import DynFlags ( mAX_PTR_TAG ) +import GHC.Driver.Session ( mAX_PTR_TAG ) import ForeignCall import Id import PrimOp diff --git a/compiler/GHC/StgToCmm/ExtCode.hs b/compiler/GHC/StgToCmm/ExtCode.hs index 2679ce4992..40472245ed 100644 --- a/compiler/GHC/StgToCmm/ExtCode.hs +++ b/compiler/GHC/StgToCmm/ExtCode.hs @@ -47,7 +47,7 @@ import GHC.Cmm.CLabel import GHC.Cmm.Graph import GHC.Cmm.BlockId -import DynFlags +import GHC.Driver.Session import FastString import Module import UniqFM diff --git a/compiler/GHC/StgToCmm/Foreign.hs b/compiler/GHC/StgToCmm/Foreign.hs index b2302a175a..04b8478c0f 100644 --- a/compiler/GHC/StgToCmm/Foreign.hs +++ b/compiler/GHC/StgToCmm/Foreign.hs @@ -37,7 +37,7 @@ import GHC.Types.RepType import GHC.Cmm.CLabel import GHC.Runtime.Heap.Layout import ForeignCall -import DynFlags +import GHC.Driver.Session import Maybes import Outputable import UniqSupply diff --git a/compiler/GHC/StgToCmm/Heap.hs b/compiler/GHC/StgToCmm/Heap.hs index 0656cb2a08..d1b1752fd3 100644 --- a/compiler/GHC/StgToCmm/Heap.hs +++ b/compiler/GHC/StgToCmm/Heap.hs @@ -45,7 +45,7 @@ import CostCentre import IdInfo( CafInfo(..), mayHaveCafRefs ) import Id ( Id ) import Module -import DynFlags +import GHC.Driver.Session import FastString( mkFastString, fsLit ) import Panic( sorry ) diff --git a/compiler/GHC/StgToCmm/Hpc.hs b/compiler/GHC/StgToCmm/Hpc.hs index 219285efbe..d52ff3fa93 100644 --- a/compiler/GHC/StgToCmm/Hpc.hs +++ b/compiler/GHC/StgToCmm/Hpc.hs @@ -18,8 +18,8 @@ import GHC.Cmm.CLabel import Module import GHC.Cmm.Utils import GHC.StgToCmm.Utils -import HscTypes -import DynFlags +import GHC.Driver.Types +import GHC.Driver.Session import Control.Monad diff --git a/compiler/GHC/StgToCmm/Layout.hs b/compiler/GHC/StgToCmm/Layout.hs index 9139c36f0b..1438077fd5 100644 --- a/compiler/GHC/StgToCmm/Layout.hs +++ b/compiler/GHC/StgToCmm/Layout.hs @@ -52,7 +52,7 @@ import GHC.Stg.Syntax import Id import TyCon ( PrimRep(..), primRepSizeB ) import BasicTypes ( RepArity ) -import DynFlags +import GHC.Driver.Session import Module import Util diff --git a/compiler/GHC/StgToCmm/Monad.hs b/compiler/GHC/StgToCmm/Monad.hs index 34709f3d67..ce01ffdb29 100644 --- a/compiler/GHC/StgToCmm/Monad.hs +++ b/compiler/GHC/StgToCmm/Monad.hs @@ -63,7 +63,7 @@ import GhcPrelude hiding( sequence, succ ) import GHC.Cmm import GHC.StgToCmm.Closure -import DynFlags +import GHC.Driver.Session import GHC.Cmm.Dataflow.Collections import GHC.Cmm.Graph as CmmGraph import GHC.Cmm.BlockId diff --git a/compiler/GHC/StgToCmm/Prim.hs b/compiler/GHC/StgToCmm/Prim.hs index 63cb5a532f..d9ab05eebb 100644 --- a/compiler/GHC/StgToCmm/Prim.hs +++ b/compiler/GHC/StgToCmm/Prim.hs @@ -35,7 +35,7 @@ import GHC.StgToCmm.Ticky import GHC.StgToCmm.Heap import GHC.StgToCmm.Prof ( costCentreFrom ) -import DynFlags +import GHC.Driver.Session import GHC.Platform import BasicTypes import GHC.Cmm.BlockId diff --git a/compiler/GHC/StgToCmm/Prof.hs b/compiler/GHC/StgToCmm/Prof.hs index 068b768073..86f20a71b9 100644 --- a/compiler/GHC/StgToCmm/Prof.hs +++ b/compiler/GHC/StgToCmm/Prof.hs @@ -36,7 +36,7 @@ import GHC.Cmm.Utils import GHC.Cmm.CLabel import CostCentre -import DynFlags +import GHC.Driver.Session import FastString import Module import Outputable diff --git a/compiler/GHC/StgToCmm/Ticky.hs b/compiler/GHC/StgToCmm/Ticky.hs index 22f91518f3..4257f02886 100644 --- a/compiler/GHC/StgToCmm/Ticky.hs +++ b/compiler/GHC/StgToCmm/Ticky.hs @@ -126,7 +126,7 @@ import FastString import Outputable import Util -import DynFlags +import GHC.Driver.Session -- Turgid imports for showTypeCategory import PrelNames diff --git a/compiler/GHC/StgToCmm/Utils.hs b/compiler/GHC/StgToCmm/Utils.hs index 3611a64f75..310bf70a7c 100644 --- a/compiler/GHC/StgToCmm/Utils.hs +++ b/compiler/GHC/StgToCmm/Utils.hs @@ -73,7 +73,7 @@ import Digraph import Util import Unique import UniqSupply (MonadUnique(..)) -import DynFlags +import GHC.Driver.Session import FastString import Outputable import GHC.Types.RepType diff --git a/compiler/backpack/NameShape.hs b/compiler/GHC/Types/Name/Shape.hs index f4c9976b48..aa1879220f 100644 --- a/compiler/backpack/NameShape.hs +++ b/compiler/GHC/Types/Name/Shape.hs @@ -1,6 +1,6 @@ {-# LANGUAGE CPP #-} -module NameShape( +module GHC.Types.Name.Shape( NameShape(..), emptyNameShape, mkNameShape, @@ -15,7 +15,7 @@ module NameShape( import GhcPrelude import Outputable -import HscTypes +import GHC.Driver.Types import Module import UniqFM import Avail diff --git a/compiler/basicTypes/Demand.hs b/compiler/basicTypes/Demand.hs index 3997bfc002..42d690a942 100644 --- a/compiler/basicTypes/Demand.hs +++ b/compiler/basicTypes/Demand.hs @@ -60,7 +60,7 @@ module Demand ( import GhcPrelude -import DynFlags +import GHC.Driver.Session import Outputable import Var ( Var ) import VarEnv diff --git a/compiler/basicTypes/Id.hs b/compiler/basicTypes/Id.hs index ff32323fd9..dddc23da10 100644 --- a/compiler/basicTypes/Id.hs +++ b/compiler/basicTypes/Id.hs @@ -119,7 +119,7 @@ module Id ( import GhcPrelude -import DynFlags +import GHC.Driver.Session import CoreSyn ( CoreRule, isStableUnfolding, evaldUnfolding, isCompulsoryUnfolding, Unfolding( NoUnfolding ) ) diff --git a/compiler/basicTypes/Literal.hs b/compiler/basicTypes/Literal.hs index 8e4d82a0f3..708a85bb2f 100644 --- a/compiler/basicTypes/Literal.hs +++ b/compiler/basicTypes/Literal.hs @@ -61,7 +61,7 @@ import FastString import BasicTypes import Binary import Constants -import DynFlags +import GHC.Driver.Session import GHC.Platform import UniqFM import Util diff --git a/compiler/basicTypes/MkId.hs b/compiler/basicTypes/MkId.hs index 5c268d37ef..6fd99f2fa3 100644 --- a/compiler/basicTypes/MkId.hs +++ b/compiler/basicTypes/MkId.hs @@ -72,7 +72,7 @@ import UniqSupply import PrelNames import BasicTypes hiding ( SuccessFlag(..) ) import Util -import DynFlags +import GHC.Driver.Session import Outputable import FastString import ListSetOps diff --git a/compiler/basicTypes/Module.hs b/compiler/basicTypes/Module.hs index 9146660254..95031f50cd 100644 --- a/compiler/basicTypes/Module.hs +++ b/compiler/basicTypes/Module.hs @@ -169,8 +169,8 @@ import qualified Data.Set as Set import qualified FiniteMap as Map import System.FilePath -import {-# SOURCE #-} DynFlags (DynFlags) -import {-# SOURCE #-} Packages (componentIdString, improveUnitId, UnitInfoMap, getUnitInfoMap, displayInstalledUnitId) +import {-# SOURCE #-} GHC.Driver.Session (DynFlags) +import {-# SOURCE #-} GHC.Driver.Packages (componentIdString, improveUnitId, UnitInfoMap, getUnitInfoMap, displayInstalledUnitId) -- Note [The identifier lexicon] -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/compiler/basicTypes/Name.hs b/compiler/basicTypes/Name.hs index 2215a4d108..418d0a3da4 100644 --- a/compiler/basicTypes/Name.hs +++ b/compiler/basicTypes/Name.hs @@ -272,7 +272,7 @@ nameIsLocalOrFrom :: Module -> Name -> Bool -- each give rise to a fresh module (Ghci1, Ghci2, etc), but they all come -- from the magic 'interactive' package; and all the details are kept in the -- TcLclEnv, TcGblEnv, NOT in the HPT or EPT. --- See Note [The interactive package] in HscTypes +-- See Note [The interactive package] in GHC.Driver.Types nameIsLocalOrFrom from name | Just mod <- nameModule_maybe name = from == mod || isInteractiveModule mod @@ -587,7 +587,7 @@ pprSystem sty uniq occ pprModulePrefix :: PprStyle -> Module -> OccName -> SDoc -- Print the "M." part of a name, based on whether it's in scope or not --- See Note [Printing original names] in HscTypes +-- See Note [Printing original names] in GHC.Driver.Types pprModulePrefix sty mod occ = ppUnlessOption sdocSuppressModulePrefixes $ case qualName sty mod occ of -- See Outputable.QualifyName: NameQual modname -> ppr modname <> dot -- Name is in scope diff --git a/compiler/basicTypes/RdrName.hs b/compiler/basicTypes/RdrName.hs index d20462c0b3..634f5eb2ec 100644 --- a/compiler/basicTypes/RdrName.hs +++ b/compiler/basicTypes/RdrName.hs @@ -1033,7 +1033,7 @@ There are two reasons for shadowing: So when we add `x = True` we must not delete the `M.x` from the `GlobalRdrEnv`; rather we just want to make it "qualified only"; hence the `mk_fake-imp_spec` in `shadowName`. See also Note - [Interactively-bound Ids in GHCi] in HscTypes + [Interactively-bound Ids in GHCi] in GHC.Driver.Types - Data types also have External Names, like Ghci4.T; but we still want 'T' to mean the newly-declared 'T', not an old one. diff --git a/compiler/coreSyn/CoreArity.hs b/compiler/coreSyn/CoreArity.hs index 79ac6244aa..abf6642633 100644 --- a/compiler/coreSyn/CoreArity.hs +++ b/compiler/coreSyn/CoreArity.hs @@ -36,7 +36,7 @@ import Predicate ( isDictTy ) import Coercion import BasicTypes import Unique -import DynFlags ( DynFlags, GeneralFlag(..), gopt ) +import GHC.Driver.Session ( DynFlags, GeneralFlag(..), gopt ) import Outputable import FastString import Util ( debugIsOn ) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index aa31aed0b5..3bdd2f8fb4 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -66,8 +66,8 @@ import OptCoercion ( checkAxInstCo ) import CoreArity ( typeArity ) import Demand ( splitStrictSig, isBotDiv ) -import HscTypes -import DynFlags +import GHC.Driver.Types +import GHC.Driver.Session import Control.Monad import qualified Control.Monad.Fail as MonadFail import MonadUtils @@ -388,7 +388,7 @@ lintInteractiveExpr what hsc_env expr interactiveInScope :: HscEnv -> [Var] -- In GHCi we may lint expressions, or bindings arising from 'deriving' -- clauses, that mention variables bound in the interactive context. --- These are Local things (see Note [Interactively-bound Ids in GHCi] in HscTypes). +-- These are Local things (see Note [Interactively-bound Ids in GHCi] in GHC.Driver.Types). -- So we have to tell Lint about them, lest it reports them as out of scope. -- -- We do this by find local-named things that may appear free in interactive diff --git a/compiler/coreSyn/CoreOpt.hs b/compiler/coreSyn/CoreOpt.hs index 1f94e5b9dc..7bb83db8b7 100644 --- a/compiler/coreSyn/CoreOpt.hs +++ b/compiler/coreSyn/CoreOpt.hs @@ -50,7 +50,7 @@ import PrelNames import BasicTypes import Module ( Module ) import ErrUtils -import DynFlags +import GHC.Driver.Session import Outputable import Pair import Util diff --git a/compiler/coreSyn/CoreSyn.hs b/compiler/coreSyn/CoreSyn.hs index 6758cebbee..2d4dd98cee 100644 --- a/compiler/coreSyn/CoreSyn.hs +++ b/compiler/coreSyn/CoreSyn.hs @@ -113,7 +113,7 @@ import Literal import DataCon import Module import BasicTypes -import DynFlags +import GHC.Driver.Session import Outputable import Util import UniqSet @@ -960,7 +960,7 @@ data Tickish id = { breakpointId :: !Int , breakpointFVs :: [id] -- ^ the order of this list is important: -- it matches the order of the lists in the - -- appropriate entry in HscTypes.ModBreaks. + -- appropriate entry in GHC.Driver.Types.ModBreaks. -- -- Careful about substitution! See -- Note [substTickish] in CoreSubst. diff --git a/compiler/coreSyn/CoreUnfold.hs b/compiler/coreSyn/CoreUnfold.hs index 1b02878bd8..ab53451fa2 100644 --- a/compiler/coreSyn/CoreUnfold.hs +++ b/compiler/coreSyn/CoreUnfold.hs @@ -46,7 +46,7 @@ module CoreUnfold ( import GhcPrelude -import DynFlags +import GHC.Driver.Session import CoreSyn import OccurAnal ( occurAnalyseExpr_NoBinderSwap ) import CoreOpt diff --git a/compiler/coreSyn/CoreUnfold.hs-boot b/compiler/coreSyn/CoreUnfold.hs-boot index 9f298f7d9d..cee6658df2 100644 --- a/compiler/coreSyn/CoreUnfold.hs-boot +++ b/compiler/coreSyn/CoreUnfold.hs-boot @@ -4,7 +4,7 @@ module CoreUnfold ( import GhcPrelude import CoreSyn -import DynFlags +import GHC.Driver.Session mkInlineUnfolding :: CoreExpr -> Unfolding diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index cde9dc0e45..7133567068 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -87,7 +87,7 @@ import TyCon import Unique import Outputable import TysPrim -import DynFlags +import GHC.Driver.Session import FastString import Maybes import ListSetOps ( minusList ) diff --git a/compiler/coreSyn/MkCore.hs b/compiler/coreSyn/MkCore.hs index e21d980775..d8b3b7a75d 100644 --- a/compiler/coreSyn/MkCore.hs +++ b/compiler/coreSyn/MkCore.hs @@ -62,7 +62,7 @@ import Var ( EvVar, setTyVarUnique ) import CoreSyn import CoreUtils ( exprType, needsCaseBinding, mkSingleAltCase, bindNonRec ) import Literal -import HscTypes +import GHC.Driver.Types import TysWiredIn import PrelNames @@ -81,7 +81,7 @@ import FastString import UniqSupply import BasicTypes import Util -import DynFlags +import GHC.Driver.Session import Data.List import Data.Char ( ord ) diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in index 04dfa692f3..5ee1e8a15c 100644 --- a/compiler/ghc.cabal.in +++ b/compiler/ghc.cabal.in @@ -160,7 +160,6 @@ Library hs-source-dirs: . - backpack basicTypes cmm coreSyn @@ -189,9 +188,9 @@ Library GHC.Iface.Ext.Ast Ar FileCleanup - DriverBkp - BkpSyn - NameShape + GHC.Driver.Backpack + GHC.Driver.Backpack.Syntax + GHC.Types.Name.Shape GHC.Iface.Rename Avail AsmUtils @@ -204,8 +203,8 @@ Library GHC.Cmm.DebugBlock Exception FieldLabel - GhcMonad - Hooks + GHC.Driver.Monad + GHC.Driver.Hooks Id IdInfo Predicate @@ -363,32 +362,32 @@ Library GHC.IfaceToCore FlagChecker Annotations - CmdLineParser - CodeOutput + GHC.Driver.CmdLine + GHC.Driver.CodeOutput Config Constants - DriverMkDepend - DriverPhases - PipelineMonad - DriverPipeline - DynFlags + GHC.Driver.MakeFile + GHC.Driver.Phases + GHC.Driver.Pipeline.Monad + GHC.Driver.Pipeline + GHC.Driver.Session ErrUtils - Finder + GHC.Driver.Finder GHC - GhcMake - GhcPlugins + GHC.Driver.Make + GHC.Plugins GhcPrelude HeaderInfo - HscMain + GHC.Driver.Main HscStats - HscTypes + GHC.Driver.Types GHC.Runtime.Eval GHC.Runtime.Eval.Types GHC.Runtime.Loader UnitInfo - Packages + GHC.Driver.Packages PlatformConstants - Plugins + GHC.Driver.Plugins TcPluginM PprTyThing Settings diff --git a/compiler/ghc.mk b/compiler/ghc.mk index de14a01646..e37a285fed 100644 --- a/compiler/ghc.mk +++ b/compiler/ghc.mk @@ -48,8 +48,8 @@ $(foreach n,1 2 3, \ $(foreach n,1 2 3, \ $(eval compiler/stage$n/package-data.mk : compiler/stage$n/build/Config.hs) \ $(eval compiler/stage$n/build/PlatformConstants.o : $(includes_GHCCONSTANTS_HASKELL_TYPE)) \ - $(eval compiler/stage$n/build/DynFlags.o: $(includes_GHCCONSTANTS_HASKELL_EXPORTS)) \ - $(eval compiler/stage$n/build/DynFlags.o: $(includes_GHCCONSTANTS_HASKELL_WRAPPERS)) \ + $(eval compiler/stage$n/build/GHC/Driver/Session.o: $(includes_GHCCONSTANTS_HASKELL_EXPORTS)) \ + $(eval compiler/stage$n/build/GHC/Driver/Session.o: $(includes_GHCCONSTANTS_HASKELL_WRAPPERS)) \ ) endif @@ -252,9 +252,9 @@ ifeq "$(GhcProfiled)" "YES" # parts of the compiler of interest, and then add further cost centres # as necessary. Turn on -fprof-auto for individual modules like this: -# compiler/main/DriverPipeline_HC_OPTS += -fprof-auto -compiler/main/GhcMake_HC_OPTS += -fprof-auto -compiler/main/GHC_HC_OPTS += -fprof-auto +# compiler/GHC/Driver/Pipeline_HC_OPTS += -fprof-auto +compiler/GHC/Driver/Make_HC_OPTS += -fprof-auto +compiler/GHC_HC_OPTS += -fprof-auto # or alternatively add {-# OPTIONS_GHC -fprof-auto #-} to the top of # modules you're interested in. diff --git a/compiler/iface/BuildTyCl.hs b/compiler/iface/BuildTyCl.hs index d9959f339f..8518b01e66 100644 --- a/compiler/iface/BuildTyCl.hs +++ b/compiler/iface/BuildTyCl.hs @@ -38,7 +38,7 @@ import Id import TcType import SrcLoc( SrcSpan, noSrcSpan ) -import DynFlags +import GHC.Driver.Session import TcRnMonad import UniqSupply import Util diff --git a/compiler/iface/FlagChecker.hs b/compiler/iface/FlagChecker.hs index aac2c24995..7cac37cb4f 100644 --- a/compiler/iface/FlagChecker.hs +++ b/compiler/iface/FlagChecker.hs @@ -11,8 +11,8 @@ module FlagChecker ( import GhcPrelude import Binary -import DynFlags -import HscTypes +import GHC.Driver.Session +import GHC.Driver.Types import Module import Name import Fingerprint diff --git a/compiler/main/Elf.hs b/compiler/main/Elf.hs index 9e19de12dd..e9c80d7d81 100644 --- a/compiler/main/Elf.hs +++ b/compiler/main/Elf.hs @@ -18,7 +18,7 @@ import GhcPrelude import AsmUtils import Exception -import DynFlags +import GHC.Driver.Session import ErrUtils import Maybes (MaybeT(..),runMaybeT) import Util (charToC) diff --git a/compiler/main/ErrUtils.hs b/compiler/main/ErrUtils.hs index 320912ba59..5adc4c61f4 100644 --- a/compiler/main/ErrUtils.hs +++ b/compiler/main/ErrUtils.hs @@ -72,7 +72,7 @@ import Outputable import Panic import qualified PprColour as Col import SrcLoc -import DynFlags +import GHC.Driver.Session import FastString (unpackFS) import StringBuffer (atLine, hGetStringBuffer, len, lexemeToString) import Json @@ -552,7 +552,7 @@ chooseDumpFile dflags dumpOpt -- by the --ddump-file-prefix flag. | Just prefix <- dumpPrefixForce dflags = Just prefix - -- dump file location chosen by DriverPipeline.runPipeline + -- dump file location chosen by GHC.Driver.Pipeline.runPipeline | Just prefix <- dumpPrefix dflags = Just prefix -- we haven't got a place to put a dump file. diff --git a/compiler/main/ErrUtils.hs-boot b/compiler/main/ErrUtils.hs-boot index a2ba51b304..e071d09272 100644 --- a/compiler/main/ErrUtils.hs-boot +++ b/compiler/main/ErrUtils.hs-boot @@ -6,7 +6,7 @@ import GhcPrelude import Outputable (SDoc, PprStyle ) import SrcLoc (SrcSpan) import Json -import {-# SOURCE #-} DynFlags ( DynFlags ) +import {-# SOURCE #-} GHC.Driver.Session ( DynFlags ) type DumpAction = DynFlags -> PprStyle -> DumpOptions -> String -> DumpFormat -> SDoc -> IO () diff --git a/compiler/main/FileCleanup.hs b/compiler/main/FileCleanup.hs index 35bed6149b..81d0ce7a40 100644 --- a/compiler/main/FileCleanup.hs +++ b/compiler/main/FileCleanup.hs @@ -9,12 +9,12 @@ module FileCleanup import GhcPrelude -import DynFlags +import GHC.Driver.Session import ErrUtils import Outputable import Util import Exception -import DriverPhases +import GHC.Driver.Phases import Control.Monad import Data.List diff --git a/compiler/main/HeaderInfo.hs b/compiler/main/HeaderInfo.hs index 4bd8a0993d..f7b2cd7fc5 100644 --- a/compiler/main/HeaderInfo.hs +++ b/compiler/main/HeaderInfo.hs @@ -23,7 +23,7 @@ module HeaderInfo ( getImports import GhcPrelude import GHC.Platform -import HscTypes +import GHC.Driver.Types import Parser ( parseHeader ) import Lexer import FastString @@ -32,7 +32,7 @@ import Module import PrelNames import StringBuffer import SrcLoc -import DynFlags +import GHC.Driver.Session import ErrUtils import Util import Outputable diff --git a/compiler/main/PprTyThing.hs b/compiler/main/PprTyThing.hs index 226986f7b5..11288618ef 100644 --- a/compiler/main/PprTyThing.hs +++ b/compiler/main/PprTyThing.hs @@ -25,7 +25,7 @@ import Type ( Type, ArgFlag(..), TyThing(..), mkTyVarBinders, tidyOpenType ) import GHC.Iface.Syntax ( ShowSub(..), ShowHowMuch(..), AltPpr(..) , showToHeader, pprIfaceDecl ) import CoAxiom ( coAxiomTyCon ) -import HscTypes( tyThingParent_maybe ) +import GHC.Driver.Types( tyThingParent_maybe ) import GHC.Iface.Utils ( tyThingToIfaceDecl ) import FamInstEnv( FamInst(..), FamFlavor(..) ) import TyCoPpr ( pprUserForAll, pprTypeApp, pprSigmaType ) diff --git a/compiler/main/StaticPtrTable.hs b/compiler/main/StaticPtrTable.hs index dfc54799d7..985e91e29c 100644 --- a/compiler/main/StaticPtrTable.hs +++ b/compiler/main/StaticPtrTable.hs @@ -119,7 +119,7 @@ Here is a running example: * If we are compiling for the byte-code interpreter, we instead explicitly add the SPT entries (recorded in CgGuts' cg_spt_entries field) to the interpreter process' SPT table using the addSptEntry interpreter message. This happens - in upsweep after we have compiled the module (see GhcMake.upsweep'). + in upsweep after we have compiled the module (see GHC.Driver.Make.upsweep'). -} import GhcPrelude @@ -128,8 +128,8 @@ import GHC.Cmm.CLabel import CoreSyn import CoreUtils (collectMakeStaticArgs) import DataCon -import DynFlags -import HscTypes +import GHC.Driver.Session +import GHC.Driver.Types import Id import MkCore (mkStringExprFSWith) import Module diff --git a/compiler/main/SysTools.hs b/compiler/main/SysTools.hs index b3312b0dae..bbe889ba99 100644 --- a/compiler/main/SysTools.hs +++ b/compiler/main/SysTools.hs @@ -43,11 +43,11 @@ import GhcPrelude import GHC.Settings import Module -import Packages +import GHC.Driver.Packages import Outputable import ErrUtils import GHC.Platform -import DynFlags +import GHC.Driver.Session import Control.Monad.Trans.Except (runExceptT) import System.FilePath diff --git a/compiler/main/SysTools/ExtraObj.hs b/compiler/main/SysTools/ExtraObj.hs index 13236933e6..9ff428f9ca 100644 --- a/compiler/main/SysTools/ExtraObj.hs +++ b/compiler/main/SysTools/ExtraObj.hs @@ -15,8 +15,8 @@ module SysTools.ExtraObj ( import AsmUtils import ErrUtils -import DynFlags -import Packages +import GHC.Driver.Session +import GHC.Driver.Packages import GHC.Platform import Outputable import SrcLoc ( noSrcSpan ) diff --git a/compiler/main/SysTools/Info.hs b/compiler/main/SysTools/Info.hs index 93c2819528..b6b74406af 100644 --- a/compiler/main/SysTools/Info.hs +++ b/compiler/main/SysTools/Info.hs @@ -10,7 +10,7 @@ module SysTools.Info where import Exception import ErrUtils -import DynFlags +import GHC.Driver.Session import Outputable import Util diff --git a/compiler/main/SysTools/Process.hs b/compiler/main/SysTools/Process.hs index c7255b6a93..8772e3eec1 100644 --- a/compiler/main/SysTools/Process.hs +++ b/compiler/main/SysTools/Process.hs @@ -12,7 +12,7 @@ module SysTools.Process where import Exception import ErrUtils -import DynFlags +import GHC.Driver.Session import FastString import Outputable import Panic diff --git a/compiler/main/SysTools/Tasks.hs b/compiler/main/SysTools/Tasks.hs index d006a84b99..e4bbb32dc6 100644 --- a/compiler/main/SysTools/Tasks.hs +++ b/compiler/main/SysTools/Tasks.hs @@ -10,8 +10,8 @@ module SysTools.Tasks where import Exception import ErrUtils -import HscTypes -import DynFlags +import GHC.Driver.Types +import GHC.Driver.Session import Outputable import GHC.Platform import Util diff --git a/compiler/main/UpdateCafInfos.hs b/compiler/main/UpdateCafInfos.hs index c5e81150fe..600dc62207 100644 --- a/compiler/main/UpdateCafInfos.hs +++ b/compiler/main/UpdateCafInfos.hs @@ -7,7 +7,7 @@ module UpdateCafInfos import GhcPrelude import CoreSyn -import HscTypes +import GHC.Driver.Types import Id import IdInfo import InstEnv diff --git a/compiler/nativeGen/AsmCodeGen.hs b/compiler/nativeGen/AsmCodeGen.hs index 4653deaab6..9aa6933757 100644 --- a/compiler/nativeGen/AsmCodeGen.hs +++ b/compiler/nativeGen/AsmCodeGen.hs @@ -84,7 +84,7 @@ import GHC.Cmm.CLabel import UniqFM import UniqSupply -import DynFlags +import GHC.Driver.Session import Util import BasicTypes ( Alignment ) diff --git a/compiler/nativeGen/BlockLayout.hs b/compiler/nativeGen/BlockLayout.hs index 3f74065e4e..e488f0908f 100644 --- a/compiler/nativeGen/BlockLayout.hs +++ b/compiler/nativeGen/BlockLayout.hs @@ -25,7 +25,7 @@ import GHC.Cmm import GHC.Cmm.Dataflow.Collections import GHC.Cmm.Dataflow.Label -import DynFlags (gopt, GeneralFlag(..), DynFlags, backendMaintainsCfg) +import GHC.Driver.Session (gopt, GeneralFlag(..), DynFlags, backendMaintainsCfg) import UniqFM import Util import Unique diff --git a/compiler/nativeGen/CFG.hs b/compiler/nativeGen/CFG.hs index f5c2a6456f..7e2c2de095 100644 --- a/compiler/nativeGen/CFG.hs +++ b/compiler/nativeGen/CFG.hs @@ -78,7 +78,7 @@ import Outputable --import OrdList --import GHC.Cmm.DebugBlock.Trace import GHC.Cmm.Ppr () -- For Outputable instances -import qualified DynFlags as D +import qualified GHC.Driver.Session as D import Data.List (sort, nub, partition) import Data.STRef.Strict diff --git a/compiler/nativeGen/Dwarf.hs b/compiler/nativeGen/Dwarf.hs index a64df287f5..5bd62a7234 100644 --- a/compiler/nativeGen/Dwarf.hs +++ b/compiler/nativeGen/Dwarf.hs @@ -9,7 +9,7 @@ import GHC.Cmm.Expr ( GlobalReg(..) ) import Config ( cProjectName, cProjectVersion ) import CoreSyn ( Tickish(..) ) import GHC.Cmm.DebugBlock -import DynFlags +import GHC.Driver.Session import Module import Outputable import GHC.Platform diff --git a/compiler/nativeGen/Instruction.hs b/compiler/nativeGen/Instruction.hs index ad4937bf08..23c5ced1d8 100644 --- a/compiler/nativeGen/Instruction.hs +++ b/compiler/nativeGen/Instruction.hs @@ -21,7 +21,7 @@ import Reg import GHC.Cmm.BlockId import GHC.Cmm.Dataflow.Collections import GHC.Cmm.Dataflow.Label -import DynFlags +import GHC.Driver.Session import GHC.Cmm hiding (topInfoTable) import GHC.Platform diff --git a/compiler/nativeGen/NCGMonad.hs b/compiler/nativeGen/NCGMonad.hs index 849b3fe761..5f2af49d4c 100644 --- a/compiler/nativeGen/NCGMonad.hs +++ b/compiler/nativeGen/NCGMonad.hs @@ -58,7 +58,7 @@ import FastString ( FastString ) import UniqFM import UniqSupply import Unique ( Unique ) -import DynFlags +import GHC.Driver.Session import Module import Control.Monad ( ap ) diff --git a/compiler/nativeGen/PIC.hs b/compiler/nativeGen/PIC.hs index 6e0708ab04..5c217f2fe6 100644 --- a/compiler/nativeGen/PIC.hs +++ b/compiler/nativeGen/PIC.hs @@ -75,7 +75,7 @@ import Module import Outputable -import DynFlags +import GHC.Driver.Session import FastString diff --git a/compiler/nativeGen/PPC/CodeGen.hs b/compiler/nativeGen/PPC/CodeGen.hs index 4374cbeb8d..ad47501981 100644 --- a/compiler/nativeGen/PPC/CodeGen.hs +++ b/compiler/nativeGen/PPC/CodeGen.hs @@ -54,7 +54,7 @@ import GHC.Cmm.Dataflow.Graph -- The rest: import OrdList import Outputable -import DynFlags +import GHC.Driver.Session import Control.Monad ( mapAndUnzipM, when ) import Data.Bits diff --git a/compiler/nativeGen/PPC/Instr.hs b/compiler/nativeGen/PPC/Instr.hs index 2dff3349fb..ad2039d463 100644 --- a/compiler/nativeGen/PPC/Instr.hs +++ b/compiler/nativeGen/PPC/Instr.hs @@ -38,7 +38,7 @@ import GHC.Platform.Regs import GHC.Cmm.BlockId import GHC.Cmm.Dataflow.Collections import GHC.Cmm.Dataflow.Label -import DynFlags +import GHC.Driver.Session import GHC.Cmm import GHC.Cmm.Info import FastString diff --git a/compiler/nativeGen/PPC/Ppr.hs b/compiler/nativeGen/PPC/Ppr.hs index 5ede19bd5e..8b81274db9 100644 --- a/compiler/nativeGen/PPC/Ppr.hs +++ b/compiler/nativeGen/PPC/Ppr.hs @@ -33,7 +33,7 @@ import Unique ( pprUniqueAlways, getUnique ) import GHC.Platform import FastString import Outputable -import DynFlags +import GHC.Driver.Session import Data.Word import Data.Int diff --git a/compiler/nativeGen/PPC/Regs.hs b/compiler/nativeGen/PPC/Regs.hs index 66aa006311..ff3ec639be 100644 --- a/compiler/nativeGen/PPC/Regs.hs +++ b/compiler/nativeGen/PPC/Regs.hs @@ -60,7 +60,7 @@ import GHC.Cmm.CLabel ( CLabel ) import Unique import GHC.Platform.Regs -import DynFlags +import GHC.Driver.Session import Outputable import GHC.Platform diff --git a/compiler/nativeGen/PprBase.hs b/compiler/nativeGen/PprBase.hs index c5574b35f0..dc6e65bd70 100644 --- a/compiler/nativeGen/PprBase.hs +++ b/compiler/nativeGen/PprBase.hs @@ -25,7 +25,7 @@ import GhcPrelude import AsmUtils import GHC.Cmm.CLabel import GHC.Cmm -import DynFlags +import GHC.Driver.Session import FastString import Outputable import GHC.Platform diff --git a/compiler/nativeGen/RegAlloc/Graph/Main.hs b/compiler/nativeGen/RegAlloc/Graph/Main.hs index 177a73bf81..6b2758f723 100644 --- a/compiler/nativeGen/RegAlloc/Graph/Main.hs +++ b/compiler/nativeGen/RegAlloc/Graph/Main.hs @@ -20,7 +20,7 @@ import RegClass import Reg import Bag -import DynFlags +import GHC.Driver.Session import Outputable import GHC.Platform import UniqFM diff --git a/compiler/nativeGen/RegAlloc/Linear/Base.hs b/compiler/nativeGen/RegAlloc/Linear/Base.hs index 3c6965c1dd..552f14929d 100644 --- a/compiler/nativeGen/RegAlloc/Linear/Base.hs +++ b/compiler/nativeGen/RegAlloc/Linear/Base.hs @@ -23,7 +23,7 @@ import RegAlloc.Linear.StackMap import RegAlloc.Liveness import Reg -import DynFlags +import GHC.Driver.Session import Outputable import Unique import UniqFM diff --git a/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs b/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs index 0feddc67d8..b2b9cff5bb 100644 --- a/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs +++ b/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs @@ -14,7 +14,7 @@ import GhcPrelude import Reg import RegClass -import DynFlags +import GHC.Driver.Session import Panic import GHC.Platform diff --git a/compiler/nativeGen/RegAlloc/Linear/JoinToTargets.hs b/compiler/nativeGen/RegAlloc/Linear/JoinToTargets.hs index d0710cb65f..4362ca8a17 100644 --- a/compiler/nativeGen/RegAlloc/Linear/JoinToTargets.hs +++ b/compiler/nativeGen/RegAlloc/Linear/JoinToTargets.hs @@ -22,7 +22,7 @@ import Reg import GHC.Cmm.BlockId import GHC.Cmm.Dataflow.Collections import Digraph -import DynFlags +import GHC.Driver.Session import Outputable import Unique import UniqFM diff --git a/compiler/nativeGen/RegAlloc/Linear/Main.hs b/compiler/nativeGen/RegAlloc/Linear/Main.hs index 7a3b1ef902..076b63a4ed 100644 --- a/compiler/nativeGen/RegAlloc/Linear/Main.hs +++ b/compiler/nativeGen/RegAlloc/Linear/Main.hs @@ -126,7 +126,7 @@ import GHC.Cmm.Dataflow.Collections import GHC.Cmm hiding (RegSet) import Digraph -import DynFlags +import GHC.Driver.Session import Unique import UniqSet import UniqFM diff --git a/compiler/nativeGen/RegAlloc/Linear/StackMap.hs b/compiler/nativeGen/RegAlloc/Linear/StackMap.hs index 95819c6fb3..79496c6e43 100644 --- a/compiler/nativeGen/RegAlloc/Linear/StackMap.hs +++ b/compiler/nativeGen/RegAlloc/Linear/StackMap.hs @@ -22,7 +22,7 @@ where import GhcPrelude -import DynFlags +import GHC.Driver.Session import UniqFM import Unique diff --git a/compiler/nativeGen/RegAlloc/Linear/State.hs b/compiler/nativeGen/RegAlloc/Linear/State.hs index d24690f04c..9e5efa5f7f 100644 --- a/compiler/nativeGen/RegAlloc/Linear/State.hs +++ b/compiler/nativeGen/RegAlloc/Linear/State.hs @@ -46,7 +46,7 @@ import Instruction import Reg import GHC.Cmm.BlockId -import DynFlags +import GHC.Driver.Session import Unique import UniqSupply diff --git a/compiler/nativeGen/RegAlloc/Liveness.hs b/compiler/nativeGen/RegAlloc/Liveness.hs index e1bbb467d0..b6fd3b3937 100644 --- a/compiler/nativeGen/RegAlloc/Liveness.hs +++ b/compiler/nativeGen/RegAlloc/Liveness.hs @@ -49,7 +49,7 @@ import GHC.Cmm.Dataflow.Label import GHC.Cmm hiding (RegSet, emptyRegSet) import Digraph -import DynFlags +import GHC.Driver.Session import MonadUtils import Outputable import GHC.Platform diff --git a/compiler/nativeGen/SPARC/Base.hs b/compiler/nativeGen/SPARC/Base.hs index 04e8fed2b3..4b3b7c984c 100644 --- a/compiler/nativeGen/SPARC/Base.hs +++ b/compiler/nativeGen/SPARC/Base.hs @@ -20,7 +20,7 @@ where import GhcPrelude -import DynFlags +import GHC.Driver.Session import Panic import Data.Int diff --git a/compiler/nativeGen/SPARC/CodeGen.hs b/compiler/nativeGen/SPARC/CodeGen.hs index 60cfd91de9..b9f79a6b9f 100644 --- a/compiler/nativeGen/SPARC/CodeGen.hs +++ b/compiler/nativeGen/SPARC/CodeGen.hs @@ -52,7 +52,7 @@ import CPrim -- The rest: import BasicTypes -import DynFlags +import GHC.Driver.Session import FastString import OrdList import Outputable diff --git a/compiler/nativeGen/SPARC/CodeGen/Base.hs b/compiler/nativeGen/SPARC/CodeGen/Base.hs index 4497e1bd5d..ba07f2311d 100644 --- a/compiler/nativeGen/SPARC/CodeGen/Base.hs +++ b/compiler/nativeGen/SPARC/CodeGen/Base.hs @@ -23,7 +23,7 @@ import Format import Reg import GHC.Platform.Regs -import DynFlags +import GHC.Driver.Session import GHC.Cmm import GHC.Cmm.Ppr.Expr () -- For Outputable instances import GHC.Platform diff --git a/compiler/nativeGen/SPARC/CodeGen/Gen32.hs b/compiler/nativeGen/SPARC/CodeGen/Gen32.hs index 01f133ed8f..4f3409ebc5 100644 --- a/compiler/nativeGen/SPARC/CodeGen/Gen32.hs +++ b/compiler/nativeGen/SPARC/CodeGen/Gen32.hs @@ -26,7 +26,7 @@ import Reg import GHC.Cmm import Control.Monad (liftM) -import DynFlags +import GHC.Driver.Session import OrdList import Outputable diff --git a/compiler/nativeGen/SPARC/CodeGen/Gen64.hs b/compiler/nativeGen/SPARC/CodeGen/Gen64.hs index a267cd22ab..7c04101ec4 100644 --- a/compiler/nativeGen/SPARC/CodeGen/Gen64.hs +++ b/compiler/nativeGen/SPARC/CodeGen/Gen64.hs @@ -24,7 +24,7 @@ import Reg import GHC.Cmm -import DynFlags +import GHC.Driver.Session import OrdList import Outputable diff --git a/compiler/nativeGen/SPARC/Instr.hs b/compiler/nativeGen/SPARC/Instr.hs index 7b4935802b..d49d82fa7e 100644 --- a/compiler/nativeGen/SPARC/Instr.hs +++ b/compiler/nativeGen/SPARC/Instr.hs @@ -41,7 +41,7 @@ import Format import GHC.Cmm.CLabel import GHC.Platform.Regs import GHC.Cmm.BlockId -import DynFlags +import GHC.Driver.Session import GHC.Cmm import FastString import Outputable diff --git a/compiler/nativeGen/SPARC/Stack.hs b/compiler/nativeGen/SPARC/Stack.hs index 3f5b2a7289..2553c6135d 100644 --- a/compiler/nativeGen/SPARC/Stack.hs +++ b/compiler/nativeGen/SPARC/Stack.hs @@ -14,7 +14,7 @@ import SPARC.Regs import SPARC.Base import SPARC.Imm -import DynFlags +import GHC.Driver.Session import Outputable -- | Get an AddrMode relative to the address in sp. diff --git a/compiler/nativeGen/X86/CodeGen.hs b/compiler/nativeGen/X86/CodeGen.hs index d60231f7b2..26797949f4 100644 --- a/compiler/nativeGen/X86/CodeGen.hs +++ b/compiler/nativeGen/X86/CodeGen.hs @@ -79,7 +79,7 @@ import ForeignCall ( CCallConv(..) ) import OrdList import Outputable import FastString -import DynFlags +import GHC.Driver.Session import Util import UniqSupply ( getUniqueM ) diff --git a/compiler/nativeGen/X86/Instr.hs b/compiler/nativeGen/X86/Instr.hs index 422bb96de4..099437265c 100644 --- a/compiler/nativeGen/X86/Instr.hs +++ b/compiler/nativeGen/X86/Instr.hs @@ -37,7 +37,7 @@ import GHC.Platform import BasicTypes (Alignment) import GHC.Cmm.CLabel -import DynFlags +import GHC.Driver.Session import UniqSet import Unique import UniqSupply diff --git a/compiler/nativeGen/X86/Ppr.hs b/compiler/nativeGen/X86/Ppr.hs index 4df7287b5a..4abc15cedd 100644 --- a/compiler/nativeGen/X86/Ppr.hs +++ b/compiler/nativeGen/X86/Ppr.hs @@ -36,7 +36,7 @@ import PprBase import GHC.Cmm.Dataflow.Collections import GHC.Cmm.Dataflow.Label import BasicTypes (Alignment, mkAlignment, alignmentBytes) -import DynFlags +import GHC.Driver.Session import GHC.Cmm hiding (topInfoTable) import GHC.Cmm.BlockId import GHC.Cmm.CLabel diff --git a/compiler/nativeGen/X86/Regs.hs b/compiler/nativeGen/X86/Regs.hs index 44f92017a1..4c8943a284 100644 --- a/compiler/nativeGen/X86/Regs.hs +++ b/compiler/nativeGen/X86/Regs.hs @@ -57,7 +57,7 @@ import RegClass import GHC.Cmm import GHC.Cmm.CLabel ( CLabel ) -import DynFlags +import GHC.Driver.Session import Outputable import GHC.Platform diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x index 7b280086ad..050a49c8c6 100644 --- a/compiler/parser/Lexer.x +++ b/compiler/parser/Lexer.x @@ -102,7 +102,7 @@ import Util ( readRational, readHexRational ) -- compiler/main import ErrUtils -import DynFlags +import GHC.Driver.Session as DynFlags -- compiler/basicTypes import SrcLoc diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 8cb9a96df1..73e3c52851 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -48,10 +48,10 @@ import qualified Prelude import GHC.Hs -- compiler/main -import DriverPhases ( HscSource(..) ) -import HscTypes ( IsBootInterface, WarningTxt(..) ) -import DynFlags -import BkpSyn +import GHC.Driver.Phases ( HscSource(..) ) +import GHC.Driver.Types ( IsBootInterface, WarningTxt(..) ) +import GHC.Driver.Session +import GHC.Driver.Backpack.Syntax import UnitInfo -- compiler/utils diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs index e8229a9443..8bf18fc928 100644 --- a/compiler/parser/RdrHsSyn.hs +++ b/compiler/parser/RdrHsSyn.hs @@ -130,7 +130,7 @@ import Maybes import Util import ApiAnnotation import Data.List -import DynFlags ( WarningFlag(..), DynFlags ) +import GHC.Driver.Session ( WarningFlag(..), DynFlags ) import ErrUtils ( Messages ) import Control.Monad diff --git a/compiler/prelude/PrelInfo.hs b/compiler/prelude/PrelInfo.hs index 221b034759..f16bb27b05 100644 --- a/compiler/prelude/PrelInfo.hs +++ b/compiler/prelude/PrelInfo.hs @@ -65,7 +65,7 @@ import MkId import Outputable import TysPrim import TysWiredIn -import HscTypes +import GHC.Driver.Types import Class import TyCon import UniqFM diff --git a/compiler/prelude/PrelNames.hs b/compiler/prelude/PrelNames.hs index 3873dbceeb..531742ea50 100644 --- a/compiler/prelude/PrelNames.hs +++ b/compiler/prelude/PrelNames.hs @@ -1505,7 +1505,7 @@ srcLocDataConName -- plugins pLUGINS :: Module -pLUGINS = mkThisGhcModule (fsLit "Plugins") +pLUGINS = mkThisGhcModule (fsLit "GHC.Driver.Plugins") pluginTyConName :: Name pluginTyConName = tcQual pLUGINS (fsLit "Plugin") pluginTyConKey frontendPluginTyConName :: Name diff --git a/compiler/prelude/PrelRules.hs b/compiler/prelude/PrelRules.hs index 72d77b07e0..201bd037f3 100644 --- a/compiler/prelude/PrelRules.hs +++ b/compiler/prelude/PrelRules.hs @@ -51,7 +51,7 @@ import Name ( Name, nameOccName ) import Outputable import FastString import BasicTypes -import DynFlags +import GHC.Driver.Session import GHC.Platform import Util import Coercion (mkUnbranchedAxInstCo,mkSymCo,Role(..)) diff --git a/compiler/profiling/ProfInit.hs b/compiler/profiling/ProfInit.hs index f8dc8822ba..411f136c98 100644 --- a/compiler/profiling/ProfInit.hs +++ b/compiler/profiling/ProfInit.hs @@ -12,7 +12,7 @@ import GhcPrelude import GHC.Cmm.CLabel import CostCentre -import DynFlags +import GHC.Driver.Session import Outputable import Module diff --git a/compiler/simplCore/CallArity.hs b/compiler/simplCore/CallArity.hs index d3709ac82a..36f80c149c 100644 --- a/compiler/simplCore/CallArity.hs +++ b/compiler/simplCore/CallArity.hs @@ -11,7 +11,7 @@ import GhcPrelude import VarSet import VarEnv -import DynFlags ( DynFlags ) +import GHC.Driver.Session ( DynFlags ) import BasicTypes import CoreSyn diff --git a/compiler/simplCore/CoreMonad.hs b/compiler/simplCore/CoreMonad.hs index 24567cb1c3..84860d56e5 100644 --- a/compiler/simplCore/CoreMonad.hs +++ b/compiler/simplCore/CoreMonad.hs @@ -52,9 +52,9 @@ module CoreMonad ( import GhcPrelude hiding ( read ) import CoreSyn -import HscTypes +import GHC.Driver.Types import Module -import DynFlags +import GHC.Driver.Session import BasicTypes ( CompilerPhase(..) ) import Annotations diff --git a/compiler/simplCore/FloatIn.hs b/compiler/simplCore/FloatIn.hs index ab66a43a04..47cbb87912 100644 --- a/compiler/simplCore/FloatIn.hs +++ b/compiler/simplCore/FloatIn.hs @@ -24,7 +24,7 @@ import GhcPrelude import CoreSyn import MkCore hiding ( wrapFloats ) -import HscTypes ( ModGuts(..) ) +import GHC.Driver.Types ( ModGuts(..) ) import CoreUtils import CoreFVs import CoreMonad ( CoreM ) @@ -33,7 +33,7 @@ import Var import Type import VarSet import Util -import DynFlags +import GHC.Driver.Session import Outputable -- import Data.List ( mapAccumL ) import BasicTypes ( RecFlag(..), isRec ) diff --git a/compiler/simplCore/FloatOut.hs b/compiler/simplCore/FloatOut.hs index a49d043e8f..18d48d4f12 100644 --- a/compiler/simplCore/FloatOut.hs +++ b/compiler/simplCore/FloatOut.hs @@ -18,7 +18,7 @@ import MkCore import CoreArity ( etaExpand ) import CoreMonad ( FloatOutSwitches(..) ) -import DynFlags +import GHC.Driver.Session import ErrUtils ( dumpIfSet_dyn, DumpFormat (..) ) import Id ( Id, idArity, idType, isBottomingId, isJoinId, isJoinId_maybe ) diff --git a/compiler/simplCore/LiberateCase.hs b/compiler/simplCore/LiberateCase.hs index 9cd21e0e18..8bea7dbfdb 100644 --- a/compiler/simplCore/LiberateCase.hs +++ b/compiler/simplCore/LiberateCase.hs @@ -11,7 +11,7 @@ module LiberateCase ( liberateCase ) where import GhcPrelude -import DynFlags +import GHC.Driver.Session import CoreSyn import CoreUnfold ( couldBeSmallEnoughToInline ) import TysWiredIn ( unitDataConId ) diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs index 35fd744b84..1acedf2b44 100644 --- a/compiler/simplCore/SimplCore.hs +++ b/compiler/simplCore/SimplCore.hs @@ -12,9 +12,9 @@ module SimplCore ( core2core, simplifyExpr ) where import GhcPrelude -import DynFlags +import GHC.Driver.Session import CoreSyn -import HscTypes +import GHC.Driver.Types import CSE ( cseProgram ) import Rules ( mkRuleBase, unionRuleBase, extendRuleBaseList, ruleCheckProgram, addRuleInfo, @@ -52,7 +52,7 @@ import WorkWrap ( wwTopBinds ) import SrcLoc import Util import Module -import Plugins ( withPlugins, installCoreToDos ) +import GHC.Driver.Plugins ( withPlugins, installCoreToDos ) import GHC.Runtime.Loader -- ( initializePlugins ) import UniqSupply ( UniqSupply, mkSplitUniqSupply, splitUniqSupply ) diff --git a/compiler/simplCore/SimplEnv.hs b/compiler/simplCore/SimplEnv.hs index 0f2d49f73f..020607abe6 100644 --- a/compiler/simplCore/SimplEnv.hs +++ b/compiler/simplCore/SimplEnv.hs @@ -57,7 +57,7 @@ import VarSet import OrdList import Id import MkCore ( mkWildValBinder ) -import DynFlags ( DynFlags ) +import GHC.Driver.Session ( DynFlags ) import TysWiredIn import qualified Type import Type hiding ( substTy, substTyVar, substTyVarBndr ) diff --git a/compiler/simplCore/SimplMonad.hs b/compiler/simplCore/SimplMonad.hs index 271f75e49b..ed0889d1b1 100644 --- a/compiler/simplCore/SimplMonad.hs +++ b/compiler/simplCore/SimplMonad.hs @@ -30,7 +30,7 @@ import Type ( Type, mkLamTypes ) import FamInstEnv ( FamInstEnv ) import CoreSyn ( RuleEnv(..) ) import UniqSupply -import DynFlags +import GHC.Driver.Session import CoreMonad import Outputable import FastString diff --git a/compiler/simplCore/SimplUtils.hs b/compiler/simplCore/SimplUtils.hs index 03c4b8ebd6..9528a73d90 100644 --- a/compiler/simplCore/SimplUtils.hs +++ b/compiler/simplCore/SimplUtils.hs @@ -42,7 +42,7 @@ import GhcPrelude import SimplEnv import CoreMonad ( SimplMode(..), Tick(..) ) -import DynFlags +import GHC.Driver.Session import CoreSyn import qualified CoreSubst import PprCore diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs index 50d35149d5..0c3e0f788b 100644 --- a/compiler/simplCore/Simplify.hs +++ b/compiler/simplCore/Simplify.hs @@ -13,7 +13,7 @@ module Simplify ( simplTopBinds, simplExpr, simplRules ) where import GhcPrelude -import DynFlags +import GHC.Driver.Session import SimplMonad import Type hiding ( substTy, substTyVar, extendTvSubst, extendCvSubst ) import SimplEnv diff --git a/compiler/specialise/Rules.hs b/compiler/specialise/Rules.hs index f90ffea54d..6b96877067 100644 --- a/compiler/specialise/Rules.hs +++ b/compiler/specialise/Rules.hs @@ -57,7 +57,7 @@ import NameEnv import UniqFM import Unify ( ruleMatchTyKiX ) import BasicTypes -import DynFlags ( DynFlags ) +import GHC.Driver.Session ( DynFlags ) import Outputable import FastString import Maybes diff --git a/compiler/specialise/SpecConstr.hs b/compiler/specialise/SpecConstr.hs index d426b3fe21..f477aed400 100644 --- a/compiler/specialise/SpecConstr.hs +++ b/compiler/specialise/SpecConstr.hs @@ -30,7 +30,7 @@ import CoreUnfold ( couldBeSmallEnoughToInline ) import CoreFVs ( exprsFreeVarsList ) import CoreMonad import Literal ( litIsLifted ) -import HscTypes ( ModGuts(..) ) +import GHC.Driver.Types ( ModGuts(..) ) import WwLib ( isWorkerSmallEnough, mkWorkerArgs ) import DataCon import Coercion hiding( substCo ) @@ -44,7 +44,7 @@ import VarEnv import VarSet import Name import BasicTypes -import DynFlags ( DynFlags(..), GeneralFlag( Opt_SpecConstrKeen ) +import GHC.Driver.Session ( DynFlags(..), GeneralFlag( Opt_SpecConstrKeen ) , gopt, hasPprDebug ) import Maybes ( orElse, catMaybes, isJust, isNothing ) import Demand diff --git a/compiler/specialise/Specialise.hs b/compiler/specialise/Specialise.hs index 0872067744..60bb890461 100644 --- a/compiler/specialise/Specialise.hs +++ b/compiler/specialise/Specialise.hs @@ -39,9 +39,9 @@ import MkId ( voidArgId, voidPrimId ) import Maybes ( mapMaybe, isJust ) import MonadUtils ( foldlM ) import BasicTypes -import HscTypes +import GHC.Driver.Types import Bag -import DynFlags +import GHC.Driver.Session import Util import Outputable import FastString diff --git a/compiler/stranal/CprAnal.hs b/compiler/stranal/CprAnal.hs index 4b9e54c11b..3691b213b8 100644 --- a/compiler/stranal/CprAnal.hs +++ b/compiler/stranal/CprAnal.hs @@ -14,7 +14,7 @@ module CprAnal ( cprAnalProgram ) where import GhcPrelude import WwLib ( deepSplitProductType_maybe ) -import DynFlags +import GHC.Driver.Session import Demand import Cpr import CoreSyn diff --git a/compiler/stranal/DmdAnal.hs b/compiler/stranal/DmdAnal.hs index d8341c143b..da771e4412 100644 --- a/compiler/stranal/DmdAnal.hs +++ b/compiler/stranal/DmdAnal.hs @@ -15,7 +15,7 @@ module DmdAnal ( dmdAnalProgram ) where import GhcPrelude -import DynFlags +import GHC.Driver.Session import WwLib ( findTypeShape ) import Demand -- All of it import CoreSyn diff --git a/compiler/stranal/WorkWrap.hs b/compiler/stranal/WorkWrap.hs index fafe0757e7..4e579d67b8 100644 --- a/compiler/stranal/WorkWrap.hs +++ b/compiler/stranal/WorkWrap.hs @@ -20,7 +20,7 @@ import IdInfo import Type import UniqSupply import BasicTypes -import DynFlags +import GHC.Driver.Session import Demand import Cpr import WwLib diff --git a/compiler/stranal/WwLib.hs b/compiler/stranal/WwLib.hs index f74243282f..8163792b5b 100644 --- a/compiler/stranal/WwLib.hs +++ b/compiler/stranal/WwLib.hs @@ -42,7 +42,7 @@ import Unique import Maybes import Util import Outputable -import DynFlags +import GHC.Driver.Session import FastString import ListSetOps diff --git a/compiler/typecheck/ClsInst.hs b/compiler/typecheck/ClsInst.hs index bcb6971f2c..41874f1807 100644 --- a/compiler/typecheck/ClsInst.hs +++ b/compiler/typecheck/ClsInst.hs @@ -39,7 +39,7 @@ import VarEnv ( VarEnv ) import DataCon import TyCon import Class -import DynFlags +import GHC.Driver.Session import Outputable import Util( splitAtList, fstOf3 ) import Data.Maybe diff --git a/compiler/typecheck/Constraint.hs b/compiler/typecheck/Constraint.hs index aa1bfe479f..9bd18504b1 100644 --- a/compiler/typecheck/Constraint.hs +++ b/compiler/typecheck/Constraint.hs @@ -98,7 +98,7 @@ import TyCoPpr import OccName import FV import VarSet -import DynFlags +import GHC.Driver.Session import BasicTypes import Outputable diff --git a/compiler/typecheck/FamInst.hs b/compiler/typecheck/FamInst.hs index 72415b331b..43ebcba8a7 100644 --- a/compiler/typecheck/FamInst.hs +++ b/compiler/typecheck/FamInst.hs @@ -15,7 +15,7 @@ module FamInst ( import GhcPrelude -import HscTypes +import GHC.Driver.Types import FamInstEnv import InstEnv( roughMatchTcs ) import Coercion @@ -27,7 +27,7 @@ import SrcLoc import TyCon import TcType import CoAxiom -import DynFlags +import GHC.Driver.Session import Module import Outputable import Util @@ -239,7 +239,7 @@ two modules are consistent--because we checked that when we compiled M. For every other pair of family instance modules we import (directly or indirectly), we check that they are consistent now. (So that we can be -certain that the modules in our `HscTypes.dep_finsts' are consistent.) +certain that the modules in our `GHC.Driver.Types.dep_finsts' are consistent.) There is some fancy footwork regarding hs-boot module loops, see Note [Don't check hs-boot type family instances too early] diff --git a/compiler/typecheck/Inst.hs b/compiler/typecheck/Inst.hs index fa6558e943..edc986f6ff 100644 --- a/compiler/typecheck/Inst.hs +++ b/compiler/typecheck/Inst.hs @@ -59,7 +59,7 @@ import Type import TyCoRep import TyCoPpr ( debugPprType ) import TcType -import HscTypes +import GHC.Driver.Types import Class( Class ) import MkId( mkDictFunId ) import CoreSyn( Expr(..) ) -- For the Coercion constructor @@ -70,7 +70,7 @@ import DataCon import VarEnv import PrelNames import SrcLoc -import DynFlags +import GHC.Driver.Session import Util import Outputable import BasicTypes ( TypeOrKind(..) ) diff --git a/compiler/typecheck/TcAnnotations.hs b/compiler/typecheck/TcAnnotations.hs index b2b9a6ffb8..5b49699eb4 100644 --- a/compiler/typecheck/TcAnnotations.hs +++ b/compiler/typecheck/TcAnnotations.hs @@ -15,7 +15,7 @@ import GhcPrelude import {-# SOURCE #-} TcSplice ( runAnnotation ) import Module -import DynFlags +import GHC.Driver.Session import Control.Monad ( when ) import GHC.Hs diff --git a/compiler/typecheck/TcBackpack.hs b/compiler/typecheck/TcBackpack.hs index 93de957b27..81445f1291 100644 --- a/compiler/typecheck/TcBackpack.hs +++ b/compiler/typecheck/TcBackpack.hs @@ -20,9 +20,9 @@ module TcBackpack ( import GhcPrelude import BasicTypes (defaultFixity, TypeOrKind(..)) -import Packages +import GHC.Driver.Packages import TcRnExports -import DynFlags +import GHC.Driver.Session import GHC.Hs import RdrName import TcRnMonad @@ -46,7 +46,7 @@ import NameEnv import NameSet import Avail import SrcLoc -import HscTypes +import GHC.Driver.Types import Outputable import Type import FastString @@ -58,9 +58,9 @@ import GHC.Iface.Syntax import PrelNames import qualified Data.Map as Map -import Finder +import GHC.Driver.Finder import UniqDSet -import NameShape +import GHC.Types.Name.Shape import TcErrors import TcUnify import GHC.Iface.Rename @@ -269,7 +269,7 @@ findExtraSigImports' hsc_env HsigFile modname = findExtraSigImports' _ _ _ = return emptyUniqDSet --- | 'findExtraSigImports', but in a convenient form for "GhcMake" and +-- | 'findExtraSigImports', but in a convenient form for "GHC.Driver.Make" and -- "TcRnDriver". findExtraSigImports :: HscEnv -> HscSource -> ModuleName -> IO [(Maybe FastString, Located ModuleName)] @@ -279,7 +279,7 @@ findExtraSigImports hsc_env hsc_src modname = do | mod_name <- uniqDSetToList extra_requirements ] -- A version of 'implicitRequirements'' which is more friendly --- for "GhcMake" and "TcRnDriver". +-- for "GHC.Driver.Make" and "TcRnDriver". implicitRequirements :: HscEnv -> [(Maybe FastString, Located ModuleName)] -> IO [(Maybe FastString, Located ModuleName)] diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs index 0f6eff4158..f597d6daf9 100644 --- a/compiler/typecheck/TcBinds.hs +++ b/compiler/typecheck/TcBinds.hs @@ -22,7 +22,7 @@ import {-# SOURCE #-} TcExpr ( tcMonoExpr ) import {-# SOURCE #-} TcPatSyn ( tcPatSynDecl, tcPatSynBuilderBind ) import CoreSyn (Tickish (..)) import CostCentre (mkUserCC, CCFlavour(DeclCC)) -import DynFlags +import GHC.Driver.Session import FastString import GHC.Hs import TcSigs diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 982a4fc395..9b79002311 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -36,7 +36,7 @@ import VarEnv( mkInScopeSet ) import VarSet( delVarSetList ) import OccName ( OccName ) import Outputable -import DynFlags( DynFlags ) +import GHC.Driver.Session( DynFlags ) import NameSet import RdrName import GHC.Hs.Types( HsIPName(..) ) diff --git a/compiler/typecheck/TcClassDcl.hs b/compiler/typecheck/TcClassDcl.hs index 60c5bd7d11..d0e62d188a 100644 --- a/compiler/typecheck/TcClassDcl.hs +++ b/compiler/typecheck/TcClassDcl.hs @@ -37,11 +37,11 @@ import Predicate import TcOrigin import TcType import TcRnMonad -import DriverPhases (HscSource(..)) +import GHC.Driver.Phases (HscSource(..)) import BuildTyCl( TcMethInfo ) import Class import Coercion ( pprCoAxiom ) -import DynFlags +import GHC.Driver.Session import FamInst import FamInstEnv import Id diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index cfa35faa35..aa5f5258df 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -19,7 +19,7 @@ module TcDeriv ( tcDeriving, DerivInfo(..) ) where import GhcPrelude import GHC.Hs -import DynFlags +import GHC.Driver.Session import TcRnMonad import FamInst diff --git a/compiler/typecheck/TcDerivUtils.hs b/compiler/typecheck/TcDerivUtils.hs index 6cf57b34f1..5bfbe51ad6 100644 --- a/compiler/typecheck/TcDerivUtils.hs +++ b/compiler/typecheck/TcDerivUtils.hs @@ -29,9 +29,9 @@ import Bag import BasicTypes import Class import DataCon -import DynFlags +import GHC.Driver.Session import ErrUtils -import HscTypes (lookupFixity, mi_fix) +import GHC.Driver.Types (lookupFixity, mi_fix) import GHC.Hs import Inst import InstEnv diff --git a/compiler/typecheck/TcEnv.hs b/compiler/typecheck/TcEnv.hs index eb1e681424..37eb4c2f98 100644 --- a/compiler/typecheck/TcEnv.hs +++ b/compiler/typecheck/TcEnv.hs @@ -96,8 +96,8 @@ import Name import NameSet import NameEnv import VarEnv -import HscTypes -import DynFlags +import GHC.Driver.Types +import GHC.Driver.Session import SrcLoc import BasicTypes hiding( SuccessFlag(..) ) import Module diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs index 24aea54adb..de38cdfcec 100644 --- a/compiler/typecheck/TcErrors.hs +++ b/compiler/typecheck/TcErrors.hs @@ -58,7 +58,7 @@ import Util import FastString import Outputable import SrcLoc -import DynFlags +import GHC.Driver.Session import ListSetOps ( equivClasses ) import Maybes import Pair diff --git a/compiler/typecheck/TcEvTerm.hs b/compiler/typecheck/TcEvTerm.hs index 60adb82839..7812339d15 100644 --- a/compiler/typecheck/TcEvTerm.hs +++ b/compiler/typecheck/TcEvTerm.hs @@ -12,8 +12,8 @@ import CoreSyn import MkCore import Literal ( Literal(..) ) import TcEvidence -import HscTypes -import DynFlags +import GHC.Driver.Types +import GHC.Driver.Session import Name import Module import CoreUtils diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs index 82f073d0a4..16b0f26ed1 100644 --- a/compiler/typecheck/TcExpr.hs +++ b/compiler/typecheck/TcExpr.hs @@ -69,7 +69,7 @@ import TysWiredIn import TysPrim( intPrimTy ) import PrimOp( tagToEnumKey ) import PrelNames -import DynFlags +import GHC.Driver.Session import SrcLoc import Util import VarEnv ( emptyTidyEnv, mkInScopeSet ) diff --git a/compiler/typecheck/TcForeign.hs b/compiler/typecheck/TcForeign.hs index 3684061642..fb17250806 100644 --- a/compiler/typecheck/TcForeign.hs +++ b/compiler/typecheck/TcForeign.hs @@ -55,12 +55,12 @@ import DataCon import TyCon import TcType import PrelNames -import DynFlags +import GHC.Driver.Session import Outputable import GHC.Platform import SrcLoc import Bag -import Hooks +import GHC.Driver.Hooks import qualified GHC.LanguageExtensions as LangExt import Control.Monad diff --git a/compiler/typecheck/TcGenDeriv.hs b/compiler/typecheck/TcGenDeriv.hs index 9c41abb6f1..4e6bbc935b 100644 --- a/compiler/typecheck/TcGenDeriv.hs +++ b/compiler/typecheck/TcGenDeriv.hs @@ -50,7 +50,7 @@ import Name import Fingerprint import Encoding -import DynFlags +import GHC.Driver.Session import PrelInfo import FamInst import FamInstEnv diff --git a/compiler/typecheck/TcGenGenerics.hs b/compiler/typecheck/TcGenGenerics.hs index 640010d45f..724da9f2e0 100644 --- a/compiler/typecheck/TcGenGenerics.hs +++ b/compiler/typecheck/TcGenGenerics.hs @@ -38,7 +38,7 @@ import TysWiredIn import PrelNames import TcEnv import TcRnMonad -import HscTypes +import GHC.Driver.Types import ErrUtils( Validity(..), andValid ) import SrcLoc import Bag diff --git a/compiler/typecheck/TcHoleErrors.hs b/compiler/typecheck/TcHoleErrors.hs index 1008bc760c..17b3c990db 100644 --- a/compiler/typecheck/TcHoleErrors.hs +++ b/compiler/typecheck/TcHoleErrors.hs @@ -37,7 +37,7 @@ import ConLike ( ConLike(..) ) import Util import TcEnv (tcLookup) import Outputable -import DynFlags +import GHC.Driver.Session import Maybes import FV ( fvVarList, fvVarSet, unionFV, mkFVs, FV ) @@ -54,7 +54,7 @@ import TcUnify ( tcSubType_NC ) import GHC.HsToCore.Docs ( extractDocs ) import qualified Data.Map as Map import GHC.Hs.Doc ( unpackHDS, DeclDocMap(..) ) -import HscTypes ( ModIface_(..) ) +import GHC.Driver.Types ( ModIface_(..) ) import GHC.Iface.Load ( loadInterfaceForNameMaybe ) import PrelInfo (knownKeyNames) diff --git a/compiler/typecheck/TcHsSyn.hs b/compiler/typecheck/TcHsSyn.hs index cf69b279e2..7dfb3ff1ab 100644 --- a/compiler/typecheck/TcHsSyn.hs +++ b/compiler/typecheck/TcHsSyn.hs @@ -69,12 +69,12 @@ import Type import Coercion import ConLike import DataCon -import HscTypes +import GHC.Driver.Types import Name import NameEnv import Var import VarEnv -import DynFlags +import GHC.Driver.Session import Literal import BasicTypes import Maybes diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index bbfe6efb5d..01e3bc19fc 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -113,7 +113,7 @@ import UniqSupply import Outputable import FastString import PrelNames hiding ( wildCardName ) -import DynFlags +import GHC.Driver.Session import qualified GHC.LanguageExtensions as LangExt import Maybes diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs index 193d6b70bb..09720f57ca 100644 --- a/compiler/typecheck/TcInstDcls.hs +++ b/compiler/typecheck/TcInstDcls.hs @@ -59,7 +59,7 @@ import VarEnv import VarSet import Bag import BasicTypes -import DynFlags +import GHC.Driver.Session import ErrUtils import FastString import Id diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index 43ec10f796..90cc412318 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -54,7 +54,7 @@ import Control.Monad import Maybes( isJust ) import Pair (Pair(..)) import Unique( hasKey ) -import DynFlags +import GHC.Driver.Session import Util import qualified GHC.LanguageExtensions as LangExt diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index 45863e4046..64a6194288 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -126,7 +126,7 @@ import FastString import Bag import Pair import UniqSet -import DynFlags +import GHC.Driver.Session import qualified GHC.LanguageExtensions as LangExt import BasicTypes ( TypeOrKind(..) ) diff --git a/compiler/typecheck/TcPat.hs b/compiler/typecheck/TcPat.hs index e610bf5182..8a3b154fe6 100644 --- a/compiler/typecheck/TcPat.hs +++ b/compiler/typecheck/TcPat.hs @@ -48,7 +48,7 @@ import PatSyn import ConLike import PrelNames import BasicTypes hiding (SuccessFlag(..)) -import DynFlags +import GHC.Driver.Session import SrcLoc import VarSet import Util diff --git a/compiler/typecheck/TcPluginM.hs b/compiler/typecheck/TcPluginM.hs index eefde31120..04aaf74816 100644 --- a/compiler/typecheck/TcPluginM.hs +++ b/compiler/typecheck/TcPluginM.hs @@ -58,7 +58,7 @@ import qualified TcEnv as TcM import qualified TcMType as TcM import qualified FamInst as TcM import qualified GHC.Iface.Env as IfaceEnv -import qualified Finder +import qualified GHC.Driver.Finder as Finder import FamInstEnv ( FamInstEnv ) import TcRnMonad ( TcGblEnv, TcLclEnv, TcPluginM @@ -76,7 +76,7 @@ import Name import TyCon import DataCon import Class -import HscTypes +import GHC.Driver.Types import Outputable import Type import Id diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs index 8d8d135d71..8f87554349 100644 --- a/compiler/typecheck/TcRnDriver.hs +++ b/compiler/typecheck/TcRnDriver.hs @@ -63,8 +63,8 @@ import GHC.Rename.Expr import GHC.Rename.Utils ( HsDocContext(..) ) import GHC.Rename.Fixity ( lookupFixityRn ) import TysWiredIn ( unitTy, mkListTy ) -import Plugins -import DynFlags +import GHC.Driver.Plugins +import GHC.Driver.Session import GHC.Hs import GHC.Iface.Syntax ( ShowSub(..), showToHeader ) import GHC.Iface.Type ( ShowForAllFlag(..) ) @@ -118,7 +118,7 @@ import NameSet import Avail import TyCon import SrcLoc -import HscTypes +import GHC.Driver.Types import ListSetOps import Outputable import ConLike @@ -1983,7 +1983,7 @@ tcRnStmt hsc_env rdr_stmt traceTc "tcs 1" empty ; this_mod <- getModule ; global_ids <- mapM (externaliseAndTidyId this_mod) zonked_ids ; - -- Note [Interactively-bound Ids in GHCi] in HscTypes + -- Note [Interactively-bound Ids in GHCi] in GHC.Driver.Types {- --------------------------------------------- At one stage I removed any shadowed bindings from the type_env; @@ -2054,7 +2054,7 @@ runPlans (p:ps) = tryTcDiscardingErrs (runPlans ps) p -- -- By 'lift' and 'environment we mean that the code is changed to -- execute properly in an IO monad. See Note [Interactively-bound Ids --- in GHCi] in HscTypes for more details. We do this lifting by trying +-- in GHCi] in GHC.Driver.Types for more details. We do this lifting by trying -- different ways ('plans') of lifting the code into the IO monad and -- type checking each plan until one succeeds. tcUserStmt :: GhciLStmt GhcPs -> TcM (PlanResult, FixityEnv) diff --git a/compiler/typecheck/TcRnExports.hs b/compiler/typecheck/TcRnExports.hs index 5a4e21d5c1..4b3f434b39 100644 --- a/compiler/typecheck/TcRnExports.hs +++ b/compiler/typecheck/TcRnExports.hs @@ -28,7 +28,7 @@ import NameSet import Avail import TyCon import SrcLoc -import HscTypes +import GHC.Driver.Types import Outputable import ConLike import DataCon @@ -39,7 +39,7 @@ import Util (capitalise) import FastString (fsLit) import Control.Monad -import DynFlags +import GHC.Driver.Session import GHC.Rename.Doc ( rnHsDoc ) import RdrHsSyn ( setRdrNameSpace ) import Data.Either ( partitionEithers ) diff --git a/compiler/typecheck/TcRnMonad.hs b/compiler/typecheck/TcRnMonad.hs index d346020963..672ba804f9 100644 --- a/compiler/typecheck/TcRnMonad.hs +++ b/compiler/typecheck/TcRnMonad.hs @@ -152,7 +152,7 @@ import TcEvidence import TcOrigin import GHC.Hs hiding (LIE) -import HscTypes +import GHC.Driver.Types import Module import RdrName import Name @@ -173,7 +173,7 @@ import NameSet import Bag import Outputable import UniqSupply -import DynFlags +import GHC.Driver.Session import FastString import Panic import Util diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index 2310b6f48a..e9da98379c 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -86,7 +86,7 @@ module TcRnTypes( import GhcPrelude import GHC.Hs -import HscTypes +import GHC.Driver.Types import TcEvidence import Type import TyCon ( TyCon, tyConKind ) @@ -115,7 +115,7 @@ import ErrUtils import UniqFM import BasicTypes import Bag -import DynFlags +import GHC.Driver.Session import Outputable import ListSetOps import Fingerprint @@ -347,7 +347,7 @@ data DsMetaVal -- module. Currently one always gets a 'FrontendTypecheck', since running the -- frontend involves typechecking a program. hs-sig merges are not handled here. -- --- This data type really should be in HscTypes, but it needs +-- This data type really should be in GHC.Driver.Types, but it needs -- to have a TcGblEnv which is only defined here. data FrontendResult = FrontendTypecheck TcGblEnv @@ -417,7 +417,7 @@ data TcGblEnv tcg_fix_env :: FixityEnv, -- ^ Just for things in this module tcg_field_env :: RecFieldEnv, -- ^ Just for things in this module - -- See Note [The interactive package] in HscTypes + -- See Note [The interactive package] in GHC.Driver.Types tcg_type_env :: TypeEnv, -- ^ Global type env for the module we are compiling now. All @@ -428,7 +428,7 @@ data TcGblEnv -- move to the global envt during zonking) -- -- NB: for what "things in this module" means, see - -- Note [The interactive package] in HscTypes + -- Note [The interactive package] in GHC.Driver.Types tcg_type_env_var :: TcRef TypeEnv, -- Used only to initialise the interface-file @@ -475,7 +475,7 @@ data TcGblEnv -- (tcRnExports) -- - imp_mods is used to compute usage info (mkIfaceTc, deSugar) -- - imp_trust_own_pkg is used for Safe Haskell in interfaces - -- (mkIfaceTc, as well as in HscMain) + -- (mkIfaceTc, as well as in GHC.Driver.Main) -- - To create the Dependencies field in interface (mkDependencies) -- These three fields track unused bindings and imports @@ -551,7 +551,7 @@ data TcGblEnv -- Things defined in this module, or (in GHCi) -- in the declarations for a single GHCi command. - -- For the latter, see Note [The interactive package] in HscTypes + -- For the latter, see Note [The interactive package] in GHC.Driver.Types tcg_tr_module :: Maybe Id, -- Id for $trModule :: GHC.Types.Module -- for which every module has a top-level defn -- except in GHCi in which case we have Nothing @@ -1326,7 +1326,7 @@ data ImportAvails -- = ModuleEnv [ImportedModsVal], -- ^ Domain is all directly-imported modules -- - -- See the documentation on ImportedModsVal in HscTypes for the + -- See the documentation on ImportedModsVal in GHC.Driver.Types for the -- meaning of the fields. -- -- We need a full ModuleEnv rather than a ModuleNameEnv here, diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index 87ff62964f..ab838be5fa 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -129,7 +129,7 @@ module TcSMonad ( import GhcPrelude -import HscTypes +import GHC.Driver.Types import qualified Inst as TcM import InstEnv @@ -143,7 +143,7 @@ import qualified TcEnv as TcM ( checkWellStaged, tcGetDefaultTys, tcLookupClass, tcLookupId, topIdLvl ) import ClsInst( InstanceWhat(..), safeOverlap, instanceReturnsDictCon ) import TcType -import DynFlags +import GHC.Driver.Session import Type import Coercion import Unify diff --git a/compiler/typecheck/TcSigs.hs b/compiler/typecheck/TcSigs.hs index 3558ebd733..95f4c846d2 100644 --- a/compiler/typecheck/TcSigs.hs +++ b/compiler/typecheck/TcSigs.hs @@ -41,7 +41,7 @@ import TcEnv( tcLookupId ) import TcEvidence( HsWrapper, (<.>) ) import Type( mkTyVarBinders ) -import DynFlags +import GHC.Driver.Session import Var ( TyVar, tyVarKind ) import Id ( Id, idName, idType, idInlinePragma, setInlinePragma, mkLocalId ) import PrelNames( mkUnboundName ) diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index b22897e720..ede2b26938 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -30,7 +30,7 @@ import GhcPrelude import Bag import Class ( Class, classKey, classTyCon ) -import DynFlags +import GHC.Driver.Session import Id ( idType, mkLocalId ) import Inst import ListSetOps @@ -507,8 +507,8 @@ How is this implemented? It's complicated! So we'll step through it all: 6) `TcRnMonad.recordUnsafeInfer` -- Save the unsafe result and reason in an IORef called `tcg_safeInfer`. - 7) `HscMain.tcRnModule'` -- Reads `tcg_safeInfer` after type-checking, calling - `HscMain.markUnsafeInfer` (passing the reason along) when safe-inferrence + 7) `GHC.Driver.Main.tcRnModule'` -- Reads `tcg_safeInfer` after type-checking, calling + `GHC.Driver.Main.markUnsafeInfer` (passing the reason along) when safe-inferrence failed. Note [No defaulting in the ambiguity check] diff --git a/compiler/typecheck/TcSplice.hs b/compiler/typecheck/TcSplice.hs index 390e088836..5acbd79084 100644 --- a/compiler/typecheck/TcSplice.hs +++ b/compiler/typecheck/TcSplice.hs @@ -38,7 +38,7 @@ import GhcPrelude import GHC.Hs import Annotations -import Finder +import GHC.Driver.Finder import Name import TcRnMonad import TcType @@ -58,12 +58,12 @@ import Control.Monad import GHCi.Message import GHCi.RemoteTypes import GHC.Runtime.Interpreter -import HscMain +import GHC.Driver.Main -- These imports are the reason that TcSplice -- is very high up the module hierarchy import GHC.Rename.Splice( traceSplice, SpliceInfo(..)) import RdrName -import HscTypes +import GHC.Driver.Types import GHC.ThToHs import GHC.Rename.Expr import GHC.Rename.Env @@ -86,7 +86,7 @@ import NameEnv import PrelNames import TysWiredIn import OccName -import Hooks +import GHC.Driver.Hooks import Var import Module import GHC.Iface.Load @@ -111,11 +111,11 @@ import Data.Maybe import FastString import BasicTypes hiding( SuccessFlag(..) ) import Maybes( MaybeErr(..) ) -import DynFlags +import GHC.Driver.Session import Panic import Lexeme import qualified EnumSet -import Plugins +import GHC.Driver.Plugins import Bag import qualified Language.Haskell.TH as TH @@ -915,7 +915,7 @@ runMeta' show_code ppr_hs run_and_convert expr ; src_span <- getSrcSpanM ; traceTc "About to run (desugared)" (ppr ds_expr) ; either_hval <- tryM $ liftIO $ - HscMain.hscCompileCoreExpr hsc_env src_span ds_expr + GHC.Driver.Main.hscCompileCoreExpr hsc_env src_span ds_expr ; case either_hval of { Left exn -> fail_with_exn "compile and link" exn ; Right hval -> do diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index da4cbdb981..05112757c9 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -29,7 +29,7 @@ module TcTyClsDecls ( import GhcPrelude import GHC.Hs -import HscTypes +import GHC.Driver.Types import BuildTyCl import TcRnMonad import TcEnv @@ -71,7 +71,7 @@ import Unify import Util import SrcLoc import ListSetOps -import DynFlags +import GHC.Driver.Session import Unique import ConLike( ConLike(..) ) import BasicTypes diff --git a/compiler/typecheck/TcTyDecls.hs b/compiler/typecheck/TcTyDecls.hs index 78104576ab..bf18c06729 100644 --- a/compiler/typecheck/TcTyDecls.hs +++ b/compiler/typecheck/TcTyDecls.hs @@ -44,7 +44,7 @@ import MkCore( rEC_SEL_ERROR_ID ) import GHC.Hs import Class import Type -import HscTypes +import GHC.Driver.Types import TyCon import ConLike import DataCon diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs index ac3820884e..27fd90f6c6 100644 --- a/compiler/typecheck/TcType.hs +++ b/compiler/typecheck/TcType.hs @@ -208,7 +208,7 @@ import GHC.Types.RepType import TyCon -- others: -import DynFlags +import GHC.Driver.Session import CoreFVs import Name -- hiding (varName) -- We use this to make dictionaries for type literals. diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs index 1568768f55..b13d70f1dd 100644 --- a/compiler/typecheck/TcTypeable.hs +++ b/compiler/typecheck/TcTypeable.hs @@ -21,7 +21,7 @@ import TcEnv import TcEvidence ( mkWpTyApps ) import TcRnMonad import TcType -import HscTypes ( lookupId ) +import GHC.Driver.Types ( lookupId ) import PrelNames import TysPrim ( primTyCons ) import TysWiredIn ( tupleTyCon, sumTyCon, runtimeRepTyCon @@ -34,7 +34,7 @@ import TyCon import DataCon import Module import GHC.Hs -import DynFlags +import GHC.Driver.Session import Bag import Var ( VarBndr(..) ) import CoreMap diff --git a/compiler/typecheck/TcUnify.hs b/compiler/typecheck/TcUnify.hs index 371cb9e108..0832f80de4 100644 --- a/compiler/typecheck/TcUnify.hs +++ b/compiler/typecheck/TcUnify.hs @@ -64,7 +64,7 @@ import Var import VarSet import VarEnv import ErrUtils -import DynFlags +import GHC.Driver.Session import BasicTypes import Bag import Util diff --git a/compiler/typecheck/TcValidity.hs b/compiler/typecheck/TcValidity.hs index 1cb4ee3dd1..385dd074a9 100644 --- a/compiler/typecheck/TcValidity.hs +++ b/compiler/typecheck/TcValidity.hs @@ -61,7 +61,7 @@ import VarSet import Var ( VarBndr(..), mkTyVar ) import FV import ErrUtils -import DynFlags +import GHC.Driver.Session import Util import ListSetOps import SrcLoc diff --git a/compiler/types/CoAxiom.hs b/compiler/types/CoAxiom.hs index a814b6e021..7d824f6c10 100644 --- a/compiler/types/CoAxiom.hs +++ b/compiler/types/CoAxiom.hs @@ -366,7 +366,7 @@ giving rise to the FamInstBranch. Note [Implicit axioms] ~~~~~~~~~~~~~~~~~~~~~~ -See also Note [Implicit TyThings] in HscTypes +See also Note [Implicit TyThings] in GHC.Driver.Types * A CoAxiom arising from data/type family instances is not "implicit". That is, it has its own IfaceAxiom declaration in an interface file diff --git a/compiler/types/OptCoercion.hs b/compiler/types/OptCoercion.hs index 40c189c0a0..f73af0edf5 100644 --- a/compiler/types/OptCoercion.hs +++ b/compiler/types/OptCoercion.hs @@ -8,7 +8,7 @@ module OptCoercion ( optCoercion, checkAxInstCo ) where import GhcPrelude -import DynFlags +import GHC.Driver.Session import TyCoRep import TyCoSubst import Coercion diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs index 7e4cc35f3b..d4bfe16a75 100644 --- a/compiler/types/TyCon.hs +++ b/compiler/types/TyCon.hs @@ -148,7 +148,7 @@ import Var import VarSet import Class import BasicTypes -import DynFlags +import GHC.Driver.Session import ForeignCall import Name import NameEnv diff --git a/compiler/utils/AsmUtils.hs b/compiler/utils/AsmUtils.hs index bb19dc2ba3..591b53dc31 100644 --- a/compiler/utils/AsmUtils.hs +++ b/compiler/utils/AsmUtils.hs @@ -1,7 +1,7 @@ -- | Various utilities used in generating assembler. -- -- These are used not only by the native code generator, but also by the --- "DriverPipeline". +-- GHC.Driver.Pipeline module AsmUtils ( sectionType ) where diff --git a/compiler/utils/IOEnv.hs b/compiler/utils/IOEnv.hs index e62a2bcddf..8067123211 100644 --- a/compiler/utils/IOEnv.hs +++ b/compiler/utils/IOEnv.hs @@ -33,7 +33,7 @@ module IOEnv ( import GhcPrelude -import DynFlags +import GHC.Driver.Session import Exception import Module import Panic diff --git a/compiler/utils/Outputable.hs b/compiler/utils/Outputable.hs index ba595757e9..b9e3993cb9 100644 --- a/compiler/utils/Outputable.hs +++ b/compiler/utils/Outputable.hs @@ -94,10 +94,11 @@ module Outputable ( import GhcPrelude -import {-# SOURCE #-} DynFlags( DynFlags, hasPprDebug, hasNoDebugOutput, - targetPlatform, pprUserLength, pprCols, - unsafeGlobalDynFlags, - initSDocContext) +import {-# SOURCE #-} GHC.Driver.Session + ( DynFlags, hasPprDebug, hasNoDebugOutput + , targetPlatform, pprUserLength, pprCols + , unsafeGlobalDynFlags, initSDocContext + ) import {-# SOURCE #-} Module( UnitId, Module, ModuleName, moduleName ) import {-# SOURCE #-} OccName( OccName ) @@ -198,7 +199,7 @@ type QueryQualifyModule = Module -> Bool -- the component id to disambiguate it. type QueryQualifyPackage = UnitId -> Bool --- See Note [Printing original names] in HscTypes +-- See Note [Printing original names] in GHC.Driver.Types data QualifyName -- Given P:M.T = NameUnqual -- It's in scope unqualified as "T" -- OR nothing called "T" is in scope diff --git a/docs/users_guide/extending_ghc.rst b/docs/users_guide/extending_ghc.rst index 4dfb4e4504..737a40c14b 100644 --- a/docs/users_guide/extending_ghc.rst +++ b/docs/users_guide/extending_ghc.rst @@ -130,7 +130,7 @@ when invoked: import GHC import GHC.Paths ( libdir ) - import DynFlags ( defaultFatalMessager, defaultFlushOut ) + import GHC.Driver.Session ( defaultFatalMessager, defaultFlushOut ) main = defaultErrorHandler defaultFatalMessager defaultFlushOut $ do @@ -324,13 +324,13 @@ Writing compiler plugins ~~~~~~~~~~~~~~~~~~~~~~~~ Plugins are modules that export at least a single identifier, -``plugin``, of type ``GhcPlugins.Plugin``. All plugins should -``import GhcPlugins`` as it defines the interface to the compilation +``plugin``, of type ``GHC.Plugins.Plugin``. All plugins should +``import GHC.Plugins`` as it defines the interface to the compilation pipeline. A ``Plugin`` effectively holds a function which installs a compilation pass into the compiler pipeline. By default there is the empty plugin -which does nothing, ``GhcPlugins.defaultPlugin``, which you should +which does nothing, ``GHC.Plugins.defaultPlugin``, which you should override with record syntax to specify your installation function. Since the exact fields of the ``Plugin`` type are open to change, this is the best way to ensure your plugins will continue to work in the future with @@ -350,7 +350,7 @@ just returns the original compilation pipeline, unmodified, and says :: module DoNothing.Plugin (plugin) where - import GhcPlugins + import GHC.Plugins plugin :: Plugin plugin = defaultPlugin { @@ -447,7 +447,7 @@ in a module it compiles: :: module SayNames.Plugin (plugin) where - import GhcPlugins + import GHC.Plugins plugin :: Plugin plugin = defaultPlugin { @@ -492,7 +492,7 @@ will print out the name of any top-level non-recursive binding with the {-# LANGUAGE DeriveDataTypeable #-} module SayAnnNames.Plugin (plugin, SomeAnn(..)) where - import GhcPlugins + import GHC.Plugins import Control.Monad (unless) import Data.Data @@ -765,9 +765,9 @@ displayed. module SourcePlugin where import Control.Monad.IO.Class - import DynFlags (getDynFlags) - import Plugins - import HscTypes + import GHC.Driver.Session (getDynFlags) + import GHC.Driver.Plugins + import GHC.Driver.Types import TcRnTypes import GHC.Hs.Extension import GHC.Hs.Decls @@ -957,7 +957,7 @@ spent on searching for valid hole fits, after which new searches are aborted. {-# LANGUAGE TypeApplications, RecordWildCards #-} module HolePlugin where - import GhcPlugins hiding ((<>)) + import GHC.Plugins hiding ((<>)) import TcHoleErrors @@ -1251,7 +1251,7 @@ we just invoke GHC with the :ghc-flag:`--frontend ⟨module⟩` flag as follows: Frontend plugins, like compiler plugins, are exported by registered plugins. However, unlike compiler modules, frontend plugins are modules that export at least a single identifier ``frontendPlugin`` of type -``GhcPlugins.FrontendPlugin``. +``GHC.Plugins.FrontendPlugin``. ``FrontendPlugin`` exports a field ``frontend``, which is a function ``[String] -> [(String, Maybe Phase)] -> Ghc ()``. The first argument @@ -1267,7 +1267,7 @@ were passed to it, and then exits. :: module DoNothing.FrontendPlugin (frontendPlugin) where - import GhcPlugins + import GHC.Plugins frontendPlugin :: FrontendPlugin frontendPlugin = defaultFrontendPlugin { @@ -1310,7 +1310,7 @@ this idea can be seen below: module DynFlagsPlugin (plugin) where import BasicTypes - import GhcPlugins + import GHC.Plugins import GHC.Hs.Expr import GHC.Hs.Extension import GHC.Hs.Lit diff --git a/ghc/GHCi/Leak.hs b/ghc/GHCi/Leak.hs index 0878f9ff5a..61a12c9a9b 100644 --- a/ghc/GHCi/Leak.hs +++ b/ghc/GHCi/Leak.hs @@ -11,7 +11,7 @@ import Foreign.Ptr (ptrToIntPtr, intPtrToPtr) import GHC import GHC.Ptr (Ptr (..)) import GHCi.Util -import HscTypes +import GHC.Driver.Types import Outputable import GHC.Platform (target32Bit) import Prelude diff --git a/ghc/GHCi/UI.hs b/ghc/GHCi/UI.hs index 6bca4e8dba..2559152954 100644 --- a/ghc/GHCi/UI.hs +++ b/ghc/GHCi/UI.hs @@ -39,25 +39,25 @@ import GHC.Runtime.Debugger import GHC.Runtime.Interpreter import GHCi.RemoteTypes import GHCi.BreakArray -import DynFlags +import GHC.Driver.Session as DynFlags import ErrUtils hiding (traceCmd) -import Finder -import GhcMonad ( modifySession ) +import GHC.Driver.Finder as Finder +import GHC.Driver.Monad ( modifySession ) import qualified GHC import GHC ( LoadHowMuch(..), Target(..), TargetId(..), InteractiveImport(..), TyThing(..), Phase, BreakIndex, Resume, SingleStep, Ghc, GetDocsFailure(..), getModuleGraph, handleSourceError ) -import HscMain (hscParseDeclsWithLocation, hscParseStmtWithLocation) +import GHC.Driver.Main (hscParseDeclsWithLocation, hscParseStmtWithLocation) import GHC.Hs.ImpExp import GHC.Hs -import HscTypes ( tyThingParent_maybe, handleFlagWarnings, getSafeMode, hsc_IC, +import GHC.Driver.Types ( tyThingParent_maybe, handleFlagWarnings, getSafeMode, hsc_IC, setInteractivePrintName, hsc_dflags, msObjFilePath, runInteractiveHsc, hsc_dynLinker ) import Module import Name -import Packages ( trusted, getPackageDetails, getInstalledPackageDetails, - listVisibleModuleNames, pprFlag ) +import GHC.Driver.Packages ( trusted, getPackageDetails, getInstalledPackageDetails, + listVisibleModuleNames, pprFlag ) import GHC.Iface.Syntax ( showToHeader ) import PprTyThing import PrelNames diff --git a/ghc/GHCi/UI/Info.hs b/ghc/GHCi/UI/Info.hs index 81e5f4db6f..7f65cf11c9 100644 --- a/ghc/GHCi/UI/Info.hs +++ b/ghc/GHCi/UI/Info.hs @@ -33,10 +33,10 @@ import System.Directory import qualified CoreUtils import GHC.HsToCore -import DynFlags (HasDynFlags(..)) +import GHC.Driver.Session (HasDynFlags(..)) import FastString import GHC -import GhcMonad +import GHC.Driver.Monad import Name import NameSet import Outputable diff --git a/ghc/GHCi/UI/Monad.hs b/ghc/GHCi/UI/Monad.hs index 6bd584bbe6..675b92babe 100644 --- a/ghc/GHCi/UI/Monad.hs +++ b/ghc/GHCi/UI/Monad.hs @@ -37,13 +37,13 @@ module GHCi.UI.Monad ( import GHCi.UI.Info (ModInfo) import qualified GHC -import GhcMonad hiding (liftIO) +import GHC.Driver.Monad hiding (liftIO) import Outputable hiding (printForUser, printForUserPartWay) import qualified Outputable import OccName -import DynFlags +import GHC.Driver.Session import FastString -import HscTypes +import GHC.Driver.Types import SrcLoc import Module import RdrName (mkOrig) diff --git a/ghc/GHCi/UI/Tags.hs b/ghc/GHCi/UI/Tags.hs index 09a8406d96..ce85bb30cf 100644 --- a/ghc/GHCi/UI/Tags.hs +++ b/ghc/GHCi/UI/Tags.hs @@ -30,7 +30,7 @@ import Data.Function import Data.List import Data.Maybe import Data.Ord -import DriverPhases +import GHC.Driver.Phases import Panic import Prelude import System.Directory diff --git a/ghc/Main.hs b/ghc/Main.hs index c30109d5aa..ab5c3323cc 100644 --- a/ghc/Main.hs +++ b/ghc/Main.hs @@ -20,21 +20,21 @@ import GHC ( -- DynFlags(..), HscTarget(..), -- GhcMode(..), GhcLink(..), Ghc, GhcMonad(..), LoadHowMuch(..) ) -import CmdLineParser +import GHC.Driver.CmdLine -- Implementations of the various modes (--show-iface, mkdependHS. etc.) -import GHC.Iface.Load ( showIface ) -import HscMain ( newHscEnv ) -import DriverPipeline ( oneShot, compileFile ) -import DriverMkDepend ( doMkDependHS ) -import DriverBkp ( doBackpack ) +import GHC.Iface.Load ( showIface ) +import GHC.Driver.Main ( newHscEnv ) +import GHC.Driver.Pipeline ( oneShot, compileFile ) +import GHC.Driver.MakeFile ( doMkDependHS ) +import GHC.Driver.Backpack ( doBackpack ) #if defined(HAVE_INTERNAL_INTERPRETER) import GHCi.UI ( interactiveUI, ghciWelcomeMsg, defaultGhciSettings ) #endif -- Frontend plugins import GHC.Runtime.Loader ( loadFrontendPlugin ) -import Plugins +import GHC.Driver.Plugins #if defined(HAVE_INTERNAL_INTERPRETER) import GHC.Runtime.Loader ( initializePlugins ) #endif @@ -47,11 +47,11 @@ import GHC.Platform import GHC.Platform.Host import Config import Constants -import HscTypes -import Packages ( pprPackages, pprPackagesSimple ) -import DriverPhases +import GHC.Driver.Types +import GHC.Driver.Packages ( pprPackages, pprPackagesSimple ) +import GHC.Driver.Phases import BasicTypes ( failed ) -import DynFlags hiding (WarnReason(..)) +import GHC.Driver.Session hiding (WarnReason(..)) import ErrUtils import FastString import Outputable @@ -66,7 +66,7 @@ import MonadUtils ( liftIO ) -- Imports for --abi-hash import GHC.Iface.Load ( loadUserInterface ) import Module ( mkModuleName ) -import Finder ( findImportedModule, cannotFindModule ) +import GHC.Driver.Finder ( findImportedModule, cannotFindModule ) import TcRnMonad ( initIfaceCheck ) import Binary ( openBinMem, put_ ) import BinFingerprint ( fingerprintBinMem ) diff --git a/hadrian/src/Settings/Packages.hs b/hadrian/src/Settings/Packages.hs index 67933d66cd..0c10549f90 100644 --- a/hadrian/src/Settings/Packages.hs +++ b/hadrian/src/Settings/Packages.hs @@ -45,13 +45,13 @@ packageArgs = do [ builder Alex ? arg "--latin1" , builder (Ghc CompileHs) ? mconcat - [ inputs ["**/GHC.hs", "**/GhcMake.hs"] ? arg "-fprof-auto" + [ inputs ["**/GHC.hs", "**/GHC/Driver/Make.hs"] ? arg "-fprof-auto" , input "**/Parser.hs" ? pure ["-fno-ignore-interface-pragmas", "-fcmm-sink"] -- These files take a very long time to compile with -O1, -- so we use -O0 for them just in Stage0 to speed up the -- build but not affect Stage1+ executables - , inputs ["**/HsInstances.hs", "**/DynFlags.hs"] ? stage0 ? + , inputs ["**/GHC/Hs/Instances.hs", "**/GHC/Driver/Session.hs"] ? stage0 ? pure ["-O0"] ] , builder (Cabal Setup) ? mconcat diff --git a/mk/config.mk.in b/mk/config.mk.in index bad99b5155..dffd00d57b 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -761,7 +761,7 @@ LdIsGNULd = @LdIsGNULd@ LdHasBuildId = @LdHasBuildId@ # Set to YES if ld has the --no_compact_unwind flag. See #5019 -# and compiler/main/DriverPipeline.hs. +# and GHC.Driver.Pipeline. LdHasNoCompactUnwind = @LdHasNoCompactUnwind@ # On MSYS, building with SplitObjs=YES fails with diff --git a/nofib b/nofib -Subproject c9fe4e92b88cd052d5fea8b713569d16c05ebf0 +Subproject cef118de79b16fc2dddc147393a46c20f126e4a diff --git a/testsuite/tests/annotations/should_run/annrun01.hs b/testsuite/tests/annotations/should_run/annrun01.hs index f8c0ca5e84..fd2c7bc415 100644 --- a/testsuite/tests/annotations/should_run/annrun01.hs +++ b/testsuite/tests/annotations/should_run/annrun01.hs @@ -5,7 +5,7 @@ module Main where import GHC import MonadUtils ( liftIO ) import Data.Maybe -import DynFlags ( defaultFatalMessager, defaultFlushOut ) +import GHC.Driver.Session ( defaultFatalMessager, defaultFlushOut ) import Annotations ( AnnTarget(..), CoreAnnTarget ) import GHC.Serialized ( deserializeWithData ) import Panic diff --git a/testsuite/tests/callarity/unittest/CallArity1.hs b/testsuite/tests/callarity/unittest/CallArity1.hs index 3b74aeaa7e..8a1cacc4e0 100644 --- a/testsuite/tests/callarity/unittest/CallArity1.hs +++ b/testsuite/tests/callarity/unittest/CallArity1.hs @@ -7,7 +7,7 @@ import MkCore import CallArity (callArityRHS) import MkId import SysTools -import DynFlags +import GHC.Driver.Session import ErrUtils import Outputable import TysWiredIn diff --git a/testsuite/tests/codeGen/should_run/T13825-unit.hs b/testsuite/tests/codeGen/should_run/T13825-unit.hs index 1c8d6e2155..5861435d9b 100644 --- a/testsuite/tests/codeGen/should_run/T13825-unit.hs +++ b/testsuite/tests/codeGen/should_run/T13825-unit.hs @@ -1,12 +1,12 @@ module Main where -import DynFlags +import GHC.Driver.Session import GHC.Types.RepType import GHC.Runtime.Heap.Layout import GHC.StgToCmm.Layout import GHC.StgToCmm.Closure import GHC -import GhcMonad +import GHC.Driver.Monad import System.Environment import GHC.Platform diff --git a/testsuite/tests/driver/T4437.hs b/testsuite/tests/driver/T4437.hs index 5187a7bf74..9ed13ed3be 100644 --- a/testsuite/tests/driver/T4437.hs +++ b/testsuite/tests/driver/T4437.hs @@ -8,7 +8,7 @@ module Main (main) where import Control.Monad import Data.List ( (\\) ) -import DynFlags +import GHC.Driver.Session import Language.Haskell.Extension main :: IO () diff --git a/testsuite/tests/ghc-api/T10508_api.hs b/testsuite/tests/ghc-api/T10508_api.hs index d0b8b0a946..f2f5574222 100644 --- a/testsuite/tests/ghc-api/T10508_api.hs +++ b/testsuite/tests/ghc-api/T10508_api.hs @@ -1,6 +1,6 @@ module Main where -import DynFlags +import GHC.Driver.Session import GHC import qualified GHC.LanguageExtensions as LangExt diff --git a/testsuite/tests/ghc-api/T10942.hs b/testsuite/tests/ghc-api/T10942.hs index 6fbf1d5bd3..53528ad718 100644 --- a/testsuite/tests/ghc-api/T10942.hs +++ b/testsuite/tests/ghc-api/T10942.hs @@ -1,6 +1,6 @@ module Main where -import DynFlags +import GHC.Driver.Session import GHC import Control.Monad.IO.Class (liftIO) diff --git a/testsuite/tests/ghc-api/T11579.hs b/testsuite/tests/ghc-api/T11579.hs index 3294f999f2..493823b843 100644 --- a/testsuite/tests/ghc-api/T11579.hs +++ b/testsuite/tests/ghc-api/T11579.hs @@ -1,5 +1,5 @@ import System.Environment -import DynFlags +import GHC.Driver.Session import FastString import GHC import StringBuffer diff --git a/testsuite/tests/ghc-api/T12099.hs b/testsuite/tests/ghc-api/T12099.hs index ba254cfd13..e9fe77d6e2 100644 --- a/testsuite/tests/ghc-api/T12099.hs +++ b/testsuite/tests/ghc-api/T12099.hs @@ -1,6 +1,6 @@ module Main where -import DynFlags +import GHC.Driver.Session import Control.Monad import Data.List (isPrefixOf) diff --git a/testsuite/tests/ghc-api/T4891/T4891.hs b/testsuite/tests/ghc-api/T4891/T4891.hs index feb792862b..58e40b5e85 100644 --- a/testsuite/tests/ghc-api/T4891/T4891.hs +++ b/testsuite/tests/ghc-api/T4891/T4891.hs @@ -7,7 +7,7 @@ import Data.Array import DataCon import GHC import GHC.Exts.Heap -import HscTypes +import GHC.Driver.Types import GHC.Runtime.Linker import GHC.Runtime.Heap.Inspect import TcEnv @@ -21,7 +21,7 @@ import Control.Monad import Data.Maybe import Bag import Outputable -import GhcMonad +import GHC.Driver.Monad import X import System.Environment diff --git a/testsuite/tests/ghc-api/T7478/T7478.hs b/testsuite/tests/ghc-api/T7478/T7478.hs index bd6fb37d8b..4aa6f7d29e 100644 --- a/testsuite/tests/ghc-api/T7478/T7478.hs +++ b/testsuite/tests/ghc-api/T7478/T7478.hs @@ -8,7 +8,7 @@ import System.Environment import GHC import qualified Config as GHC import qualified Outputable as GHC -import GhcMonad (liftIO) +import GHC.Driver.Monad (liftIO) import Outputable (PprStyle, queryQual) compileInGhc :: [FilePath] -- ^ Targets diff --git a/testsuite/tests/ghc-api/T8628.hs b/testsuite/tests/ghc-api/T8628.hs index d3b05a9f86..983adf8636 100644 --- a/testsuite/tests/ghc-api/T8628.hs +++ b/testsuite/tests/ghc-api/T8628.hs @@ -1,7 +1,7 @@ module Main where import System.IO -import DynFlags +import GHC.Driver.Session import GHC import Exception import Module diff --git a/testsuite/tests/ghc-api/T8639_api.hs b/testsuite/tests/ghc-api/T8639_api.hs index 2b0bc7d4c6..eab7ff9146 100644 --- a/testsuite/tests/ghc-api/T8639_api.hs +++ b/testsuite/tests/ghc-api/T8639_api.hs @@ -1,7 +1,7 @@ module Main where import GHC -import GhcMonad +import GHC.Driver.Monad import Outputable import System.IO import System.Environment( getArgs ) diff --git a/testsuite/tests/ghc-api/T9015.hs b/testsuite/tests/ghc-api/T9015.hs index 977390b88e..228449041d 100644 --- a/testsuite/tests/ghc-api/T9015.hs +++ b/testsuite/tests/ghc-api/T9015.hs @@ -1,9 +1,9 @@ module Main where import GHC -import DynFlags +import GHC.Driver.Session import System.Environment -import GhcMonad +import GHC.Driver.Monad testStrings = [ "import Data.Maybe" diff --git a/testsuite/tests/ghc-api/T9595.hs b/testsuite/tests/ghc-api/T9595.hs index 0f71d7700b..a4c3dea7e4 100644 --- a/testsuite/tests/ghc-api/T9595.hs +++ b/testsuite/tests/ghc-api/T9595.hs @@ -1,11 +1,11 @@ module Main where import GHC -import Packages -import GhcMonad +import GHC.Driver.Packages +import GHC.Driver.Monad import Outputable import System.Environment -import DynFlags +import GHC.Driver.Session import Module main = diff --git a/testsuite/tests/ghc-api/annotations-literals/literals.hs b/testsuite/tests/ghc-api/annotations-literals/literals.hs index 9243eba0b7..c125ea6e43 100644 --- a/testsuite/tests/ghc-api/annotations-literals/literals.hs +++ b/testsuite/tests/ghc-api/annotations-literals/literals.hs @@ -7,7 +7,7 @@ import Data.Data import Data.List (intercalate) import System.IO import GHC -import DynFlags +import GHC.Driver.Session import MonadUtils import Outputable import Bag (filterBag,isEmptyBag) diff --git a/testsuite/tests/ghc-api/annotations-literals/parsed.hs b/testsuite/tests/ghc-api/annotations-literals/parsed.hs index cba17fe4c3..352aae6e17 100644 --- a/testsuite/tests/ghc-api/annotations-literals/parsed.hs +++ b/testsuite/tests/ghc-api/annotations-literals/parsed.hs @@ -8,7 +8,7 @@ import Data.Data import Data.List (intercalate) import System.IO import GHC -import DynFlags +import GHC.Driver.Session import MonadUtils import Outputable import Bag (filterBag,isEmptyBag) diff --git a/testsuite/tests/ghc-api/annotations/CheckUtils.hs b/testsuite/tests/ghc-api/annotations/CheckUtils.hs index cdcec69029..a43348bcda 100644 --- a/testsuite/tests/ghc-api/annotations/CheckUtils.hs +++ b/testsuite/tests/ghc-api/annotations/CheckUtils.hs @@ -9,7 +9,7 @@ import Data.List import System.IO import GHC import BasicTypes -import DynFlags +import GHC.Driver.Session import MonadUtils import Outputable import ApiAnnotation diff --git a/testsuite/tests/ghc-api/annotations/annotations.hs b/testsuite/tests/ghc-api/annotations/annotations.hs index a9d54a422b..d9157511aa 100644 --- a/testsuite/tests/ghc-api/annotations/annotations.hs +++ b/testsuite/tests/ghc-api/annotations/annotations.hs @@ -9,7 +9,7 @@ import Data.Data import Data.List (intercalate) import System.IO import GHC -import DynFlags +import GHC.Driver.Session import MonadUtils import Outputable import Bag (filterBag,isEmptyBag) diff --git a/testsuite/tests/ghc-api/annotations/comments.hs b/testsuite/tests/ghc-api/annotations/comments.hs index 128a69f15e..8a36043e55 100644 --- a/testsuite/tests/ghc-api/annotations/comments.hs +++ b/testsuite/tests/ghc-api/annotations/comments.hs @@ -9,7 +9,7 @@ import Data.Data import Data.List (intercalate) import System.IO import GHC -import DynFlags +import GHC.Driver.Session import MonadUtils import Outputable import Bag (filterBag,isEmptyBag) diff --git a/testsuite/tests/ghc-api/annotations/listcomps.hs b/testsuite/tests/ghc-api/annotations/listcomps.hs index 313da7c750..8af3bf6b69 100644 --- a/testsuite/tests/ghc-api/annotations/listcomps.hs +++ b/testsuite/tests/ghc-api/annotations/listcomps.hs @@ -10,7 +10,7 @@ import Data.List (intercalate) import System.IO import GHC import BasicTypes -import DynFlags +import GHC.Driver.Session import MonadUtils import Outputable import ApiAnnotation diff --git a/testsuite/tests/ghc-api/annotations/parseTree.hs b/testsuite/tests/ghc-api/annotations/parseTree.hs index 453cade21d..be72c7f195 100644 --- a/testsuite/tests/ghc-api/annotations/parseTree.hs +++ b/testsuite/tests/ghc-api/annotations/parseTree.hs @@ -10,7 +10,7 @@ import Data.List (intercalate) import System.IO import GHC import BasicTypes -import DynFlags +import GHC.Driver.Session import MonadUtils import Outputable import Bag (filterBag,isEmptyBag) diff --git a/testsuite/tests/ghc-api/annotations/stringSource.hs b/testsuite/tests/ghc-api/annotations/stringSource.hs index 9c5d114211..698d93a6e2 100644 --- a/testsuite/tests/ghc-api/annotations/stringSource.hs +++ b/testsuite/tests/ghc-api/annotations/stringSource.hs @@ -12,7 +12,7 @@ import Data.List (intercalate) import System.IO import GHC import BasicTypes -import DynFlags +import GHC.Driver.Session import FastString import ForeignCall import MonadUtils diff --git a/testsuite/tests/ghc-api/annotations/t11430.hs b/testsuite/tests/ghc-api/annotations/t11430.hs index 81c070c01c..f1022805cf 100644 --- a/testsuite/tests/ghc-api/annotations/t11430.hs +++ b/testsuite/tests/ghc-api/annotations/t11430.hs @@ -12,7 +12,7 @@ import Data.List (intercalate) import System.IO import GHC import BasicTypes -import DynFlags +import GHC.Driver.Session import FastString import ForeignCall import MonadUtils diff --git a/testsuite/tests/ghc-api/apirecomp001/myghc.hs b/testsuite/tests/ghc-api/apirecomp001/myghc.hs index 799382cac8..fba7dd3d48 100644 --- a/testsuite/tests/ghc-api/apirecomp001/myghc.hs +++ b/testsuite/tests/ghc-api/apirecomp001/myghc.hs @@ -10,7 +10,7 @@ module Main where import GHC -import DynFlags +import GHC.Driver.Session import MonadUtils ( MonadIO(..) ) import BasicTypes ( failed ) import Bag ( bagToList ) diff --git a/testsuite/tests/ghc-api/downsweep/OldModLocation.hs b/testsuite/tests/ghc-api/downsweep/OldModLocation.hs index 96bd4deb58..d3aeddd0bc 100644 --- a/testsuite/tests/ghc-api/downsweep/OldModLocation.hs +++ b/testsuite/tests/ghc-api/downsweep/OldModLocation.hs @@ -1,9 +1,9 @@ {-# LANGUAGE ViewPatterns #-} import GHC -import GhcMake -import DynFlags -import Finder +import GHC.Driver.Make +import GHC.Driver.Session +import GHC.Driver.Finder import Control.Monad.IO.Class (liftIO) import Data.List (sort, stripPrefix) diff --git a/testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs b/testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs index 86e6b9d650..df6a2b63f6 100644 --- a/testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs +++ b/testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs @@ -4,8 +4,8 @@ -- kinds of parse errors occur in modules. import GHC -import GhcMake -import DynFlags +import GHC.Driver.Make +import GHC.Driver.Session import Outputable import Exception (ExceptionMonad, ghandle) import Bag diff --git a/testsuite/tests/ghc-api/target-contents/TargetContents.hs b/testsuite/tests/ghc-api/target-contents/TargetContents.hs index 33e73e8991..04d97c108a 100644 --- a/testsuite/tests/ghc-api/target-contents/TargetContents.hs +++ b/testsuite/tests/ghc-api/target-contents/TargetContents.hs @@ -2,7 +2,7 @@ module Main where -import DynFlags +import GHC.Driver.Session import GHC import Control.Monad @@ -13,7 +13,7 @@ import Data.Time.Calendar import Data.Time.Clock import Exception import HeaderInfo -import HscTypes +import GHC.Driver.Types import Outputable import StringBuffer import System.Directory diff --git a/testsuite/tests/ghci/should_run/tc-plugin-ghci/TcPluginGHCi.hs b/testsuite/tests/ghci/should_run/tc-plugin-ghci/TcPluginGHCi.hs index c8a3bb6d34..9d0ed01491 100644 --- a/testsuite/tests/ghci/should_run/tc-plugin-ghci/TcPluginGHCi.hs +++ b/testsuite/tests/ghci/should_run/tc-plugin-ghci/TcPluginGHCi.hs @@ -1,7 +1,7 @@ module TcPluginGHCi where import TcRnMonad ( TcPlugin(..), TcPluginResult(..) ) -import Plugins ( defaultPlugin, Plugin(..), CommandLineOption ) +import GHC.Driver.Plugins ( defaultPlugin, Plugin(..), CommandLineOption ) import Debug.Trace plugin :: Plugin diff --git a/testsuite/tests/hiefile/should_run/PatTypes.hs b/testsuite/tests/hiefile/should_run/PatTypes.hs index 352b8f1070..5d67639339 100644 --- a/testsuite/tests/hiefile/should_run/PatTypes.hs +++ b/testsuite/tests/hiefile/should_run/PatTypes.hs @@ -12,7 +12,7 @@ import GHC.Iface.Ext.Binary import GHC.Iface.Ext.Types import GHC.Iface.Ext.Utils -import DynFlags +import GHC.Driver.Session import SysTools import qualified Data.Map as M diff --git a/testsuite/tests/parser/should_run/CountParserDeps.hs b/testsuite/tests/parser/should_run/CountParserDeps.hs index f3dc6e6154..0fedc62dca 100644 --- a/testsuite/tests/parser/should_run/CountParserDeps.hs +++ b/testsuite/tests/parser/should_run/CountParserDeps.hs @@ -10,10 +10,10 @@ module Main(main) where -- provided with as small a number of modules as possible for when the -- need exists to produce ASTs and nothing more. -import HscTypes +import GHC.Driver.Types import Module -import DynFlags -import HscMain +import GHC.Driver.Session +import GHC.Driver.Main import GHC import Util import Data.Maybe diff --git a/testsuite/tests/plugins/FrontendPlugin.hs b/testsuite/tests/plugins/FrontendPlugin.hs index 8a223beae9..e264cc4062 100644 --- a/testsuite/tests/plugins/FrontendPlugin.hs +++ b/testsuite/tests/plugins/FrontendPlugin.hs @@ -1,11 +1,11 @@ module FrontendPlugin where -import GhcPlugins +import GHC.Plugins import qualified GHC import GHC ( Ghc, LoadHowMuch(..) ) -import DriverPipeline hiding ( hsc_env ) -import DriverPhases +import GHC.Driver.Pipeline hiding ( hsc_env ) +import GHC.Driver.Phases import System.Exit import Control.Monad import Data.List (partition) diff --git a/testsuite/tests/plugins/HomePackagePlugin.hs b/testsuite/tests/plugins/HomePackagePlugin.hs index 7c979c3fb5..d2b11dd81a 100644 --- a/testsuite/tests/plugins/HomePackagePlugin.hs +++ b/testsuite/tests/plugins/HomePackagePlugin.hs @@ -1,6 +1,6 @@ module HomePackagePlugin where -import GhcPlugins +import GHC.Plugins plugin :: Plugin plugin = defaultPlugin { diff --git a/testsuite/tests/plugins/LinkerTicklingPlugin.hs b/testsuite/tests/plugins/LinkerTicklingPlugin.hs index 260d4c1228..7b7fc12a62 100644 --- a/testsuite/tests/plugins/LinkerTicklingPlugin.hs +++ b/testsuite/tests/plugins/LinkerTicklingPlugin.hs @@ -1,7 +1,7 @@ module LinkerTicklingPlugin where -import GhcPlugins -import DynFlags +import GHC.Plugins +import GHC.Driver.Session plugin :: Plugin plugin = defaultPlugin { diff --git a/testsuite/tests/plugins/T16104-plugin/T16104_Plugin.hs b/testsuite/tests/plugins/T16104-plugin/T16104_Plugin.hs index 79cd0fe16d..c85b4ca395 100644 --- a/testsuite/tests/plugins/T16104-plugin/T16104_Plugin.hs +++ b/testsuite/tests/plugins/T16104-plugin/T16104_Plugin.hs @@ -2,7 +2,7 @@ module T16104_Plugin (plugin) where -import GhcPlugins +import GHC.Plugins import Data.Bits plugin :: Plugin diff --git a/testsuite/tests/plugins/annotation-plugin/SayAnnNames.hs b/testsuite/tests/plugins/annotation-plugin/SayAnnNames.hs index ae4135d203..1db2693c6b 100644 --- a/testsuite/tests/plugins/annotation-plugin/SayAnnNames.hs +++ b/testsuite/tests/plugins/annotation-plugin/SayAnnNames.hs @@ -1,6 +1,6 @@ {-# LANGUAGE DeriveDataTypeable #-} module SayAnnNames (plugin, SomeAnn(..)) where -import GhcPlugins +import GHC.Plugins import Control.Monad (unless) import Data.Data diff --git a/testsuite/tests/plugins/hole-fit-plugin/HoleFitPlugin.hs b/testsuite/tests/plugins/hole-fit-plugin/HoleFitPlugin.hs index 2692dbe665..054df8af3c 100644 --- a/testsuite/tests/plugins/hole-fit-plugin/HoleFitPlugin.hs +++ b/testsuite/tests/plugins/hole-fit-plugin/HoleFitPlugin.hs @@ -1,7 +1,7 @@ {-# LANGUAGE TypeApplications, RecordWildCards #-} module HoleFitPlugin where -import GhcPlugins hiding ((<>)) +import GHC.Plugins hiding ((<>)) import TcHoleErrors diff --git a/testsuite/tests/plugins/hooks-plugin/Hooks/Plugin.hs b/testsuite/tests/plugins/hooks-plugin/Hooks/Plugin.hs index 04e066c22f..ab3a1e26e3 100644 --- a/testsuite/tests/plugins/hooks-plugin/Hooks/Plugin.hs +++ b/testsuite/tests/plugins/hooks-plugin/Hooks/Plugin.hs @@ -2,11 +2,11 @@ module Hooks.Plugin (plugin) where import BasicTypes -import GhcPlugins +import GHC.Plugins import GHC.Hs.Expr import GHC.Hs.Extension import GHC.Hs.Lit -import Hooks +import GHC.Driver.Hooks import TcRnMonad plugin :: Plugin diff --git a/testsuite/tests/plugins/plugin-recomp/Common.hs b/testsuite/tests/plugins/plugin-recomp/Common.hs index ce4f8240c8..0ba2b36202 100644 --- a/testsuite/tests/plugins/plugin-recomp/Common.hs +++ b/testsuite/tests/plugins/plugin-recomp/Common.hs @@ -1,7 +1,7 @@ {-# LANGUAGE CPP #-} module Common where -import GhcPlugins +import GHC.Plugins install :: [CommandLineOption] -> [CoreToDo] -> CoreM [CoreToDo] install options todos = do diff --git a/testsuite/tests/plugins/plugin-recomp/FingerprintPlugin.hs b/testsuite/tests/plugins/plugin-recomp/FingerprintPlugin.hs index 584962470a..41c0de44f1 100644 --- a/testsuite/tests/plugins/plugin-recomp/FingerprintPlugin.hs +++ b/testsuite/tests/plugins/plugin-recomp/FingerprintPlugin.hs @@ -1,6 +1,6 @@ module FingerprintPlugin where -import GhcPlugins +import GHC.Plugins import Common plugin :: Plugin diff --git a/testsuite/tests/plugins/plugin-recomp/ImpurePlugin.hs b/testsuite/tests/plugins/plugin-recomp/ImpurePlugin.hs index 0ccb626a15..2a123e561f 100644 --- a/testsuite/tests/plugins/plugin-recomp/ImpurePlugin.hs +++ b/testsuite/tests/plugins/plugin-recomp/ImpurePlugin.hs @@ -1,6 +1,6 @@ module ImpurePlugin where -import GhcPlugins +import GHC.Plugins import Common plugin :: Plugin diff --git a/testsuite/tests/plugins/plugin-recomp/PurePlugin.hs b/testsuite/tests/plugins/plugin-recomp/PurePlugin.hs index c106aa3400..acc319531c 100644 --- a/testsuite/tests/plugins/plugin-recomp/PurePlugin.hs +++ b/testsuite/tests/plugins/plugin-recomp/PurePlugin.hs @@ -1,6 +1,6 @@ module PurePlugin where -import GhcPlugins +import GHC.Plugins import Common plugin :: Plugin diff --git a/testsuite/tests/plugins/rule-defining-plugin/RuleDefiningPlugin.hs b/testsuite/tests/plugins/rule-defining-plugin/RuleDefiningPlugin.hs index ad6657129c..5552ae0194 100644 --- a/testsuite/tests/plugins/rule-defining-plugin/RuleDefiningPlugin.hs +++ b/testsuite/tests/plugins/rule-defining-plugin/RuleDefiningPlugin.hs @@ -1,6 +1,6 @@ module RuleDefiningPlugin where -import GhcPlugins +import GHC.Plugins {-# RULES "unsound" forall x. show x = "SHOWED" #-} diff --git a/testsuite/tests/plugins/simple-plugin/Simple/Plugin.hs b/testsuite/tests/plugins/simple-plugin/Simple/Plugin.hs index aabc1e5b6c..91ecb6d44b 100644 --- a/testsuite/tests/plugins/simple-plugin/Simple/Plugin.hs +++ b/testsuite/tests/plugins/simple-plugin/Simple/Plugin.hs @@ -3,7 +3,7 @@ module Simple.Plugin(plugin) where import UniqFM -import GhcPlugins +import GHC.Plugins import qualified ErrUtils -- For annotation tests diff --git a/testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs b/testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs index b0ede20d41..4ca8d3fee3 100644 --- a/testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs +++ b/testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs @@ -3,9 +3,9 @@ module Simple.RemovePlugin where import Control.Monad.IO.Class import Data.List (intercalate) -import Plugins +import GHC.Driver.Plugins import Bag -import HscTypes +import GHC.Driver.Types import TcRnTypes import GHC.Hs.Extension import GHC.Hs.Expr diff --git a/testsuite/tests/plugins/simple-plugin/Simple/SourcePlugin.hs b/testsuite/tests/plugins/simple-plugin/Simple/SourcePlugin.hs index cb5fc70550..c16eea0c64 100644 --- a/testsuite/tests/plugins/simple-plugin/Simple/SourcePlugin.hs +++ b/testsuite/tests/plugins/simple-plugin/Simple/SourcePlugin.hs @@ -3,8 +3,8 @@ module Simple.SourcePlugin where import Control.Monad.IO.Class import Data.List (intercalate) import Data.Maybe (isJust) -import Plugins -import HscTypes +import GHC.Driver.Plugins +import GHC.Driver.Types import TcRnTypes import GHC.Hs.Extension import Avail diff --git a/testsuite/tests/plugins/simple-plugin/Simple/TrustworthyPlugin.hs b/testsuite/tests/plugins/simple-plugin/Simple/TrustworthyPlugin.hs index c2b4568de3..fb5df22e7d 100644 --- a/testsuite/tests/plugins/simple-plugin/Simple/TrustworthyPlugin.hs +++ b/testsuite/tests/plugins/simple-plugin/Simple/TrustworthyPlugin.hs @@ -1,6 +1,6 @@ module Simple.TrustworthyPlugin (plugin) where -import GhcPlugins +import GHC.Plugins import TcRnMonad plugin :: Plugin diff --git a/testsuite/tests/plugins/static-plugins.hs b/testsuite/tests/plugins/static-plugins.hs index 3dd6aa2e6d..77d451451a 100644 --- a/testsuite/tests/plugins/static-plugins.hs +++ b/testsuite/tests/plugins/static-plugins.hs @@ -2,7 +2,7 @@ module Main where import Avail import Control.Monad.IO.Class -import DynFlags +import GHC.Driver.Session (getDynFlags, parseDynamicFlagsCmdLine, defaultFatalMessager, defaultFlushOut) import GHC import GHC.Fingerprint.Type @@ -11,9 +11,9 @@ import GHC.Hs.Doc import GHC.Hs.Expr import GHC.Hs.Extension import GHC.Hs.ImpExp -import HscTypes +import GHC.Driver.Types import Outputable -import Plugins +import GHC.Driver.Plugins import System.Environment import TcRnTypes diff --git a/testsuite/tests/quasiquotation/T7918.hs b/testsuite/tests/quasiquotation/T7918.hs index 507f4b3ee8..a5a2ddfb70 100644 --- a/testsuite/tests/quasiquotation/T7918.hs +++ b/testsuite/tests/quasiquotation/T7918.hs @@ -2,7 +2,7 @@ module Main (main) where import GHC -import DynFlags +import GHC.Driver.Session import Outputable import MonadUtils import NameSet diff --git a/testsuite/tests/regalloc/regalloc_unit_tests.hs b/testsuite/tests/regalloc/regalloc_unit_tests.hs index cf632f1cd5..0732b03fbb 100644 --- a/testsuite/tests/regalloc/regalloc_unit_tests.hs +++ b/testsuite/tests/regalloc/regalloc_unit_tests.hs @@ -23,7 +23,7 @@ module Main where import qualified RegAlloc.Graph.Stats as Color import qualified RegAlloc.Linear.Base as Linear import qualified X86.Instr -import HscMain +import GHC.Driver.Main import GHC.StgToCmm.CgUtils import AsmCodeGen import GHC.Cmm.Info.Build @@ -34,10 +34,10 @@ import GHC.Cmm import Module import GHC.Cmm.DebugBlock import GHC -import GhcMonad +import GHC.Driver.Monad import UniqFM import UniqSupply -import DynFlags +import GHC.Driver.Session import ErrUtils import Outputable import BasicTypes diff --git a/testsuite/tests/rts/linker/LinkerUnload.hs b/testsuite/tests/rts/linker/LinkerUnload.hs index d26fae57ea..d534be795d 100644 --- a/testsuite/tests/rts/linker/LinkerUnload.hs +++ b/testsuite/tests/rts/linker/LinkerUnload.hs @@ -1,7 +1,7 @@ module LinkerUnload (init) where import GHC -import DynFlags +import GHC.Driver.Session import GHC.Runtime.Linker as Linker import System.Environment import MonadUtils ( MonadIO(..) ) diff --git a/testsuite/tests/simplCore/should_compile/T7702plugin/T7702Plugin.hs b/testsuite/tests/simplCore/should_compile/T7702plugin/T7702Plugin.hs index e411d04e67..f063ab7615 100644 --- a/testsuite/tests/simplCore/should_compile/T7702plugin/T7702Plugin.hs +++ b/testsuite/tests/simplCore/should_compile/T7702plugin/T7702Plugin.hs @@ -1,6 +1,6 @@ module T7702Plugin ( plugin ) where -import GhcPlugins +import GHC.Plugins -- A plugin that does nothing but tickle CoreM's writer. plugin :: Plugin diff --git a/testsuite/tests/typecheck/should_compile/T11462_Plugin.hs b/testsuite/tests/typecheck/should_compile/T11462_Plugin.hs index 5d98395d6a..bc57d16089 100644 --- a/testsuite/tests/typecheck/should_compile/T11462_Plugin.hs +++ b/testsuite/tests/typecheck/should_compile/T11462_Plugin.hs @@ -1,7 +1,7 @@ module T11462_Plugin(plugin) where import TcRnMonad ( TcPlugin(..), TcPluginResult(..) ) -import Plugins ( defaultPlugin, Plugin(..), CommandLineOption ) +import GHC.Driver.Plugins ( defaultPlugin, Plugin(..), CommandLineOption ) plugin :: Plugin plugin = defaultPlugin { tcPlugin = Just . thePlugin } diff --git a/testsuite/tests/typecheck/should_compile/T11525_Plugin.hs b/testsuite/tests/typecheck/should_compile/T11525_Plugin.hs index bc1ffc4da0..5133b87b7f 100644 --- a/testsuite/tests/typecheck/should_compile/T11525_Plugin.hs +++ b/testsuite/tests/typecheck/should_compile/T11525_Plugin.hs @@ -1,7 +1,7 @@ module T11525_Plugin(plugin) where import TcRnMonad ( TcPlugin(..), TcPluginResult(..) ) -import Plugins ( defaultPlugin, Plugin(..), CommandLineOption ) +import GHC.Driver.Plugins ( defaultPlugin, Plugin(..), CommandLineOption ) plugin :: Plugin plugin = defaultPlugin { tcPlugin = Just . thePlugin } diff --git a/testsuite/tests/unboxedsums/unboxedsums_unit_tests.hs b/testsuite/tests/unboxedsums/unboxedsums_unit_tests.hs index 73552d63f9..1614b7ce42 100644 --- a/testsuite/tests/unboxedsums/unboxedsums_unit_tests.hs +++ b/testsuite/tests/unboxedsums/unboxedsums_unit_tests.hs @@ -2,7 +2,7 @@ module Main where import BasicTypes import GHC -import GhcMonad +import GHC.Driver.Monad import Outputable import GHC.Types.RepType import TysPrim diff --git a/utils/check-api-annotations/Main.hs b/utils/check-api-annotations/Main.hs index 14af201967..51d389ce13 100644 --- a/utils/check-api-annotations/Main.hs +++ b/utils/check-api-annotations/Main.hs @@ -3,7 +3,7 @@ import Data.Data import Data.List import GHC -import DynFlags +import GHC.Driver.Session import Outputable import ApiAnnotation import SrcLoc diff --git a/utils/check-ppr/Main.hs b/utils/check-ppr/Main.hs index c2bbe95ba1..227e47d0b5 100644 --- a/utils/check-ppr/Main.hs +++ b/utils/check-ppr/Main.hs @@ -4,7 +4,7 @@ import Data.List import SrcLoc import GHC hiding (moduleName) import GHC.Hs.Dump -import DynFlags +import GHC.Driver.Session import Outputable hiding (space) import System.Environment( getArgs ) import System.Exit diff --git a/utils/haddock b/utils/haddock -Subproject 40591606251693956d9729ab3a15c7244d7fc2a +Subproject 70c86ff53f97ed9b6a41b90c61357de2ac44d70 |