summaryrefslogtreecommitdiff
path: root/compiler/GHC/Iface
diff options
context:
space:
mode:
authorSylvain Henry <sylvain@haskus.fr>2020-10-15 17:55:34 +0200
committerMarge Bot <ben+marge-bot@smart-cactus.org>2020-10-29 03:53:52 -0400
commit0e9f6defbdc1f691ff7197b21e68ac16ffa4ab59 (patch)
tree1c9d9848db07596c19221fd195db81cdf6430385 /compiler/GHC/Iface
parent795908dc4eab8e8b40cb318a2adbe4a4d4126c74 (diff)
downloadhaskell-0e9f6defbdc1f691ff7197b21e68ac16ffa4ab59.tar.gz
Split GHC.Driver.Types
I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule
Diffstat (limited to 'compiler/GHC/Iface')
-rw-r--r--compiler/GHC/Iface/Binary.hs2
-rw-r--r--compiler/GHC/Iface/Env.hs36
-rw-r--r--compiler/GHC/Iface/Ext/Ast.hs6
-rw-r--r--compiler/GHC/Iface/Ext/Fields.hs94
-rw-r--r--compiler/GHC/Iface/Load.hs60
-rw-r--r--compiler/GHC/Iface/Load.hs-boot2
-rw-r--r--compiler/GHC/Iface/Make.hs44
-rw-r--r--compiler/GHC/Iface/Recomp.hs42
-rw-r--r--compiler/GHC/Iface/Recomp/Flags.hs2
-rw-r--r--compiler/GHC/Iface/Rename.hs33
-rw-r--r--compiler/GHC/Iface/Syntax.hs13
-rw-r--r--compiler/GHC/Iface/Tidy.hs44
-rw-r--r--compiler/GHC/Iface/Tidy/StaticPtrTable.hs20
-rw-r--r--compiler/GHC/Iface/Type.hs4
-rw-r--r--compiler/GHC/Iface/UpdateIdInfos.hs8
15 files changed, 308 insertions, 102 deletions
diff --git a/compiler/GHC/Iface/Binary.hs b/compiler/GHC/Iface/Binary.hs
index 5eddac0373..e2a6f0a79b 100644
--- a/compiler/GHC/Iface/Binary.hs
+++ b/compiler/GHC/Iface/Binary.hs
@@ -39,8 +39,8 @@ import GHC.Prelude
import GHC.Tc.Utils.Monad
import GHC.Builtin.Utils ( isKnownKeyName, lookupKnownKeyName )
import GHC.Iface.Env
-import GHC.Driver.Types
import GHC.Unit
+import GHC.Unit.Module.ModIface
import GHC.Types.Name
import GHC.Driver.Session
import GHC.Platform.Profile
diff --git a/compiler/GHC/Iface/Env.hs b/compiler/GHC/Iface/Env.hs
index 161384821b..4b4567289c 100644
--- a/compiler/GHC/Iface/Env.hs
+++ b/compiler/GHC/Iface/Env.hs
@@ -16,7 +16,7 @@ module GHC.Iface.Env (
ifaceExportNames,
-- Name-cache stuff
- allocateGlobalBinder, updNameCacheTc,
+ allocateGlobalBinder, updNameCacheTc, updNameCache,
mkNameCacheUpdater, NameCacheUpdater(..),
) where
@@ -24,22 +24,29 @@ module GHC.Iface.Env (
import GHC.Prelude
+import GHC.Driver.Env
+
import GHC.Tc.Utils.Monad
-import GHC.Driver.Types
import GHC.Core.Type
-import GHC.Types.Var
-import GHC.Types.Name
-import GHC.Types.Avail
+import GHC.Iface.Type
+import GHC.Runtime.Context
+
import GHC.Unit.Module
+import GHC.Unit.Module.ModIface
+
import GHC.Data.FastString
import GHC.Data.FastString.Env
-import GHC.Iface.Type
+
+import GHC.Types.Var
+import GHC.Types.Name
+import GHC.Types.Avail
import GHC.Types.Name.Cache
import GHC.Types.Unique.Supply
import GHC.Types.SrcLoc
import GHC.Utils.Outputable
import Data.List ( partition )
+import Data.IORef
{-
*********************************************************
@@ -296,3 +303,20 @@ newIfaceNames occs
= do { uniqs <- newUniqueSupply
; return [ mkInternalName uniq occ noSrcSpan
| (occ,uniq) <- occs `zip` uniqsFromSupply uniqs] }
+
+{-
+Names in a NameCache are always stored as a Global, and have the SrcLoc
+of their binding locations.
+
+Actually that's not quite right. When we first encounter the original
+name, we might not be at its binding site (e.g. we are reading an
+interface file); so we give it 'noSrcLoc' then. Later, when we find
+its binding site, we fix it up.
+-}
+
+updNameCache :: IORef NameCache
+ -> (NameCache -> (NameCache, c)) -- The updating function
+ -> IO c
+updNameCache ncRef upd_fn
+ = atomicModifyIORef' ncRef upd_fn
+
diff --git a/compiler/GHC/Iface/Ext/Ast.hs b/compiler/GHC/Iface/Ext/Ast.hs
index 01c5b6102f..f13cbf30b3 100644
--- a/compiler/GHC/Iface/Ext/Ast.hs
+++ b/compiler/GHC/Iface/Ext/Ast.hs
@@ -37,8 +37,7 @@ import GHC.Core.DataCon ( dataConNonlinearType )
import GHC.HsToCore ( deSugarExpr )
import GHC.Types.FieldLabel
import GHC.Hs
-import GHC.Driver.Types
-import GHC.Unit.Module ( ModuleName, ml_hs_file )
+import GHC.Driver.Env
import GHC.Utils.Monad ( concatMapM, liftIO )
import GHC.Types.Id ( isDataConId_maybe )
import GHC.Types.Name ( Name, nameSrcSpan, nameUnique )
@@ -62,6 +61,9 @@ import GHC.Data.FastString
import GHC.Iface.Ext.Types
import GHC.Iface.Ext.Utils
+import GHC.Unit.Module ( ModuleName, ml_hs_file )
+import GHC.Unit.Module.ModSummary
+
import qualified Data.Array as A
import qualified Data.ByteString as BS
import qualified Data.Map as M
diff --git a/compiler/GHC/Iface/Ext/Fields.hs b/compiler/GHC/Iface/Ext/Fields.hs
new file mode 100644
index 0000000000..1cc1e94012
--- /dev/null
+++ b/compiler/GHC/Iface/Ext/Fields.hs
@@ -0,0 +1,94 @@
+module GHC.Iface.Ext.Fields
+ ( ExtensibleFields (..)
+ , FieldName
+ , emptyExtensibleFields
+ -- * Reading
+ , readField
+ , readFieldWith
+ -- * Writing
+ , writeField
+ , writeFieldWith
+ -- * Deletion
+ , deleteField
+ )
+where
+
+import GHC.Prelude
+import GHC.Utils.Binary
+
+import Control.Monad
+import Data.Map ( Map )
+import qualified Data.Map as Map
+import Control.DeepSeq
+
+type FieldName = String
+
+newtype ExtensibleFields = ExtensibleFields { getExtensibleFields :: (Map FieldName BinData) }
+
+instance Binary ExtensibleFields where
+ put_ bh (ExtensibleFields fs) = do
+ put_ bh (Map.size fs :: Int)
+
+ -- Put the names of each field, and reserve a space
+ -- for a payload pointer after each name:
+ header_entries <- forM (Map.toList fs) $ \(name, dat) -> do
+ put_ bh name
+ field_p_p <- tellBin bh
+ put_ bh field_p_p
+ return (field_p_p, dat)
+
+ -- Now put the payloads and use the reserved space
+ -- to point to the start of each payload:
+ forM_ header_entries $ \(field_p_p, dat) -> do
+ field_p <- tellBin bh
+ putAt bh field_p_p field_p
+ seekBin bh field_p
+ put_ bh dat
+
+ get bh = do
+ n <- get bh :: IO Int
+
+ -- Get the names and field pointers:
+ header_entries <- replicateM n $ do
+ (,) <$> get bh <*> get bh
+
+ -- Seek to and get each field's payload:
+ fields <- forM header_entries $ \(name, field_p) -> do
+ seekBin bh field_p
+ dat <- get bh
+ return (name, dat)
+
+ return . ExtensibleFields . Map.fromList $ fields
+
+instance NFData ExtensibleFields where
+ rnf (ExtensibleFields fs) = rnf fs
+
+emptyExtensibleFields :: ExtensibleFields
+emptyExtensibleFields = ExtensibleFields Map.empty
+
+--------------------------------------------------------------------------------
+-- | Reading
+
+readField :: Binary a => FieldName -> ExtensibleFields -> IO (Maybe a)
+readField name = readFieldWith name get
+
+readFieldWith :: FieldName -> (BinHandle -> IO a) -> ExtensibleFields -> IO (Maybe a)
+readFieldWith name read fields = sequence $ ((read =<<) . dataHandle) <$>
+ Map.lookup name (getExtensibleFields fields)
+
+--------------------------------------------------------------------------------
+-- | Writing
+
+writeField :: Binary a => FieldName -> a -> ExtensibleFields -> IO ExtensibleFields
+writeField name x = writeFieldWith name (`put_` x)
+
+writeFieldWith :: FieldName -> (BinHandle -> IO ()) -> ExtensibleFields -> IO ExtensibleFields
+writeFieldWith name write fields = do
+ bh <- openBinMem (1024 * 1024)
+ write bh
+ --
+ bd <- handleData bh
+ return $ ExtensibleFields (Map.insert name bd $ getExtensibleFields fields)
+
+deleteField :: FieldName -> ExtensibleFields -> ExtensibleFields
+deleteField name (ExtensibleFields fs) = ExtensibleFields $ Map.delete name fs
diff --git a/compiler/GHC/Iface/Load.hs b/compiler/GHC/Iface/Load.hs
index 212bcb78ac..ed8ecf0e08 100644
--- a/compiler/GHC/Iface/Load.hs
+++ b/compiler/GHC/Iface/Load.hs
@@ -40,49 +40,69 @@ import {-# SOURCE #-} GHC.IfaceToCore
( tcIfaceDecl, tcIfaceRules, tcIfaceInst, tcIfaceFamInst
, tcIfaceAnnotations, tcIfaceCompleteMatches )
+import GHC.Driver.Env
import GHC.Driver.Session
import GHC.Driver.Backend
import GHC.Driver.Ppr
+import GHC.Driver.Hooks
+import GHC.Driver.Plugins
+
import GHC.Iface.Syntax
import GHC.Iface.Env
-import GHC.Driver.Types
+import GHC.Iface.Ext.Fields
+import GHC.Iface.Binary
+import GHC.Iface.Rename
-import GHC.Types.Basic hiding (SuccessFlag(..))
import GHC.Tc.Utils.Monad
import GHC.Utils.Binary ( BinData(..) )
+import GHC.Utils.Error
+import GHC.Utils.Outputable as Outputable
+import GHC.Utils.Panic
+import GHC.Utils.Misc
+import GHC.Utils.Fingerprint
+
import GHC.Settings.Constants
+
import GHC.Builtin.Names
import GHC.Builtin.Utils
import GHC.Builtin.PrimOps ( allThePrimOps, primOpFixity, primOpOcc )
-import GHC.Types.Id.Make ( seqId, EnableBignumRules(..) )
+
import GHC.Core.Rules
import GHC.Core.TyCon
-import GHC.Types.Annotations
import GHC.Core.InstEnv
import GHC.Core.FamInstEnv
+
+import GHC.Types.Id.Make ( seqId, EnableBignumRules(..) )
+import GHC.Types.Annotations
import GHC.Types.Name
import GHC.Types.Name.Env
import GHC.Types.Avail
-import GHC.Unit.Module
-import GHC.Unit.State
-import GHC.Data.Maybe
-import GHC.Utils.Error
-import GHC.Driver.Finder
+import GHC.Types.Fixity
+import GHC.Types.Fixity.Env
+import GHC.Types.SourceError
+import GHC.Types.SourceText
+import GHC.Types.SourceFile
+import GHC.Types.SafeHaskell
+import GHC.Types.TypeEnv
import GHC.Types.Unique.FM
+import GHC.Types.Unique.DSet
import GHC.Types.SrcLoc
-import GHC.Utils.Outputable as Outputable
-import GHC.Iface.Binary
-import GHC.Utils.Panic
-import GHC.Utils.Misc
-import GHC.Data.FastString
-import GHC.Utils.Fingerprint
-import GHC.Driver.Hooks
import GHC.Types.FieldLabel
-import GHC.Iface.Rename
-import GHC.Types.Unique.DSet
-import GHC.Driver.Plugins
+import GHC.Types.TyThing
+
+import GHC.Unit.External
+import GHC.Unit.Module
+import GHC.Unit.Module.Warnings
+import GHC.Unit.Module.ModIface
+import GHC.Unit.Module.Deps
+import GHC.Unit.State
import GHC.Unit.Home
+import GHC.Unit.Home.ModInfo
+import GHC.Unit.Finder
+
+import GHC.Data.Maybe
+import GHC.Data.FastString
import Control.Monad
import Control.Exception
@@ -873,7 +893,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 GHC.Driver.Types).
+in one-shot mode; see notes with hsc_HPT decl in GHC.Driver.Env).
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 78c5dd2e67..0e83000eba 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 GHC.Unit.Module (Module)
import GHC.Tc.Utils.Monad (IfM)
-import GHC.Driver.Types (ModIface)
+import GHC.Unit.Module.ModIface (ModIface)
import GHC.Utils.Outputable (SDoc)
loadSysInterface :: SDoc -> Module -> IfM lcl ModIface
diff --git a/compiler/GHC/Iface/Make.hs b/compiler/GHC/Iface/Make.hs
index 27933fc18e..4c369e0bc4 100644
--- a/compiler/GHC/Iface/Make.hs
+++ b/compiler/GHC/Iface/Make.hs
@@ -23,15 +23,21 @@ where
import GHC.Prelude
+import GHC.Hs
+
+import GHC.StgToCmm.Types (CgInfos (..))
+
+import GHC.Tc.Utils.TcType
+import GHC.Tc.Utils.Monad
+
import GHC.Iface.Syntax
import GHC.Iface.Recomp
import GHC.Iface.Load
+import GHC.Iface.Ext.Fields
+
import GHC.CoreToIface
import qualified GHC.LanguageExtensions as LangExt
-import GHC.HsToCore.Usage ( mkUsageInfo, mkUsedNames, mkDependencies )
-import GHC.Types.Id
-import GHC.Types.Annotations
import GHC.Core
import GHC.Core.Class
import GHC.Core.TyCon
@@ -40,16 +46,19 @@ import GHC.Core.ConLike
import GHC.Core.DataCon
import GHC.Core.Type
import GHC.Core.Multiplicity
-import GHC.StgToCmm.Types (CgInfos (..))
-import GHC.Tc.Utils.TcType
import GHC.Core.InstEnv
import GHC.Core.FamInstEnv
-import GHC.Tc.Utils.Monad
-import GHC.Hs
-import GHC.Driver.Types
+
+import GHC.Driver.Env
import GHC.Driver.Backend
import GHC.Driver.Session
import GHC.Driver.Ppr
+import GHC.Driver.Plugins (LoadedPlugin(..))
+
+import GHC.Types.Id
+import GHC.Types.Fixity.Env
+import GHC.Types.SafeHaskell
+import GHC.Types.Annotations
import GHC.Types.Var.Env
import GHC.Types.Var
import GHC.Types.Name
@@ -58,21 +67,34 @@ import GHC.Types.Name.Reader
import GHC.Types.Name.Env
import GHC.Types.Name.Set
import GHC.Types.Unique.DSet
-import GHC.Unit
+import GHC.Types.Basic hiding ( SuccessFlag(..) )
+import GHC.Types.TypeEnv
+import GHC.Types.SourceFile
+import GHC.Types.TyThing
+import GHC.Types.HpcInfo
+
import GHC.Utils.Error
import GHC.Utils.Outputable
import GHC.Utils.Panic
-import GHC.Types.Basic hiding ( SuccessFlag(..) )
import GHC.Utils.Misc hiding ( eqListBy )
+
import GHC.Data.FastString
import GHC.Data.Maybe
+
import GHC.HsToCore.Docs
+import GHC.HsToCore.Usage ( mkUsageInfo, mkUsedNames, mkDependencies )
+
+import GHC.Unit
+import GHC.Unit.Module.Warnings
+import GHC.Unit.Module.ModIface
+import GHC.Unit.Module.ModDetails
+import GHC.Unit.Module.ModGuts
+import GHC.Unit.Module.Deps
import Data.Function
import Data.List ( findIndex, mapAccumL, sortBy )
import Data.Ord
import Data.IORef
-import GHC.Driver.Plugins (LoadedPlugin(..))
{-
************************************************************************
diff --git a/compiler/GHC/Iface/Recomp.hs b/compiler/GHC/Iface/Recomp.hs
index 68df3e2fbd..c810911509 100644
--- a/compiler/GHC/Iface/Recomp.hs
+++ b/compiler/GHC/Iface/Recomp.hs
@@ -14,45 +14,57 @@ where
import GHC.Prelude
+import GHC.Driver.Backend
+import GHC.Driver.Env
+import GHC.Driver.Session
+import GHC.Driver.Ppr
+import GHC.Driver.Plugins ( PluginRecompile(..), PluginWithArgs(..), pluginRecompile', plugins )
+
import GHC.Iface.Syntax
import GHC.Iface.Recomp.Binary
import GHC.Iface.Load
import GHC.Iface.Recomp.Flags
-import GHC.Types.Annotations
import GHC.Core
import GHC.Tc.Utils.Monad
import GHC.Hs
-import GHC.Driver.Backend
-import GHC.Driver.Types
-import GHC.Driver.Finder
-import GHC.Driver.Session
-import GHC.Driver.Ppr
-import GHC.Types.Name
-import GHC.Types.Name.Set
-import GHC.Unit.Module
+
+import GHC.Data.Graph.Directed
+import GHC.Data.Maybe
+import GHC.Data.FastString
+
import GHC.Utils.Error
import GHC.Utils.Panic
-import GHC.Data.Graph.Directed
-import GHC.Types.SrcLoc
import GHC.Utils.Outputable as Outputable
-import GHC.Types.Unique
import GHC.Utils.Misc as Utils hiding ( eqListBy )
-import GHC.Data.Maybe
-import GHC.Data.FastString
import GHC.Utils.Binary
import GHC.Utils.Fingerprint
import GHC.Utils.Exception
+
+import GHC.Types.Annotations
+import GHC.Types.Name
+import GHC.Types.Name.Set
+import GHC.Types.SrcLoc
+import GHC.Types.Unique
import GHC.Types.Unique.Set
+import GHC.Types.Fixity.Env
+import GHC.Types.SourceFile
+
+import GHC.Unit.External
+import GHC.Unit.Finder
import GHC.Unit.State
import GHC.Unit.Home
+import GHC.Unit.Module
+import GHC.Unit.Module.ModIface
+import GHC.Unit.Module.ModSummary
+import GHC.Unit.Module.Warnings
+import GHC.Unit.Module.Deps
import Control.Monad
import Data.Function
import Data.List (find, sortBy, sort)
import qualified Data.Map as Map
import qualified Data.Set as Set
-import GHC.Driver.Plugins ( PluginRecompile(..), PluginWithArgs(..), pluginRecompile', plugins )
--Qualified import so we can define a Semigroup instance
-- but it doesn't clash with Outputable.<>
diff --git a/compiler/GHC/Iface/Recomp/Flags.hs b/compiler/GHC/Iface/Recomp/Flags.hs
index 28419149b5..e73c061018 100644
--- a/compiler/GHC/Iface/Recomp/Flags.hs
+++ b/compiler/GHC/Iface/Recomp/Flags.hs
@@ -12,9 +12,9 @@ import GHC.Prelude
import GHC.Utils.Binary
import GHC.Driver.Session
-import GHC.Driver.Types
import GHC.Unit.Module
import GHC.Types.Name
+import GHC.Types.SafeHaskell
import GHC.Utils.Fingerprint
import GHC.Iface.Recomp.Binary
-- import GHC.Utils.Outputable
diff --git a/compiler/GHC/Iface/Rename.hs b/compiler/GHC/Iface/Rename.hs
index 63ca80af12..749914821a 100644
--- a/compiler/GHC/Iface/Rename.hs
+++ b/compiler/GHC/Iface/Rename.hs
@@ -18,35 +18,40 @@ module GHC.Iface.Rename (
import GHC.Prelude
-import GHC.Types.SrcLoc
-import GHC.Utils.Outputable
-import GHC.Driver.Types
+import GHC.Driver.Session
+import GHC.Driver.Env
+
+import GHC.Tc.Utils.Monad
+
+import GHC.Iface.Syntax
+import GHC.Iface.Env
+import {-# SOURCE #-} GHC.Iface.Load -- a bit vexing
+
import GHC.Unit
import GHC.Unit.State
+import GHC.Unit.Module.ModIface
+import GHC.Unit.Module.Deps
+
+import GHC.Types.SrcLoc
import GHC.Types.Unique.FM
import GHC.Types.Avail
-import GHC.Iface.Syntax
import GHC.Types.FieldLabel
import GHC.Types.Var
-import GHC.Utils.Error
-
+import GHC.Types.Basic
import GHC.Types.Name
-import GHC.Tc.Utils.Monad
+import GHC.Types.Name.Shape
+
+import GHC.Utils.Error
+import GHC.Utils.Outputable
import GHC.Utils.Misc
import GHC.Utils.Fingerprint
import GHC.Utils.Panic
-import GHC.Types.Basic
--- a bit vexing
-import {-# SOURCE #-} GHC.Iface.Load
-import GHC.Driver.Session
+import GHC.Data.Bag
import qualified Data.Traversable as T
-import GHC.Data.Bag
import Data.IORef
-import GHC.Types.Name.Shape
-import GHC.Iface.Env
tcRnMsgMaybe :: IO (Either ErrorMessages a) -> TcM a
tcRnMsgMaybe do_this = do
diff --git a/compiler/GHC/Iface/Syntax.hs b/compiler/GHC/Iface/Syntax.hs
index 3def579fb7..72ff681c99 100644
--- a/compiler/GHC/Iface/Syntax.hs
+++ b/compiler/GHC/Iface/Syntax.hs
@@ -73,6 +73,7 @@ import GHC.Builtin.Types ( constraintKindTyConName )
import GHC.Utils.Lexeme (isLexSym)
import GHC.Utils.Fingerprint
import GHC.Utils.Binary
+import GHC.Utils.Binary.Typeable ()
import GHC.Utils.Outputable as Outputable
import GHC.Utils.Panic
import GHC.Utils.Misc( dropList, filterByList, notNull, unzipWith, debugIsOn,
@@ -194,7 +195,7 @@ data IfaceTyConParent
| IfDataInstance
IfExtName -- Axiom name
IfaceTyCon -- Family TyCon (pretty-printing only, not used in GHC.IfaceToCore)
- -- see Note [Pretty printing via Iface syntax] in GHC.Core.Ppr.TyThing
+ -- see Note [Pretty printing via Iface syntax] in GHC.Types.TyThing.Ppr
IfaceAppArgs -- Arguments of the family TyCon
data IfaceFamTyConFlav
@@ -203,7 +204,7 @@ data IfaceFamTyConFlav
| IfaceClosedSynFamilyTyCon (Maybe (IfExtName, [IfaceAxBranch]))
-- ^ Name of associated axiom and branches for pretty printing purposes,
-- or 'Nothing' for an empty closed family without an axiom
- -- See Note [Pretty printing via Iface syntax] in "GHC.Core.Ppr.TyThing"
+ -- See Note [Pretty printing via Iface syntax] in "GHC.Types.TyThing.Ppr"
| IfaceAbstractClosedSynFamilyTyCon
| IfaceBuiltInSynFamTyCon -- for pretty printing purposes only
@@ -463,10 +464,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 GHC.Driver.Types
+-- See Note [Implicit TyThings] in GHC.Driver.Env
-- N.B. the set of names returned here *must* match the set of
--- TyThings returned by GHC.Driver.Types.implicitTyThings, in the sense that
+-- TyThings returned by GHC.Driver.Env.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.
@@ -736,7 +737,7 @@ Note [Printing IfaceDecl binders]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The binders in an IfaceDecl are just OccNames, so we don't know what module they
come from. But when we pretty-print a TyThing by converting to an IfaceDecl
-(see GHC.Core.Ppr.TyThing), the TyThing may come from some other module so we really need
+(see GHC.Types.TyThing.Ppr), the TyThing may come from some other module so we really need
the module qualifier. We solve this by passing in a pretty-printer for the
binders.
@@ -806,7 +807,7 @@ constraintIfaceKind =
pprIfaceDecl :: ShowSub -> IfaceDecl -> SDoc
-- NB: pprIfaceDecl is also used for pretty-printing TyThings in GHCi
--- See Note [Pretty-printing TyThings] in GHC.Core.Ppr.TyThing
+-- See Note [Pretty-printing TyThings] in GHC.Types.TyThing.Ppr
pprIfaceDecl ss (IfaceData { ifName = tycon, ifCType = ctype,
ifCtxt = context, ifResKind = kind,
ifRoles = roles, ifCons = condecls,
diff --git a/compiler/GHC/Iface/Tidy.hs b/compiler/GHC/Iface/Tidy.hs
index 82f1c18920..10d0eb1d04 100644
--- a/compiler/GHC/Iface/Tidy.hs
+++ b/compiler/GHC/Iface/Tidy.hs
@@ -17,10 +17,13 @@ module GHC.Iface.Tidy (
import GHC.Prelude
-import GHC.Tc.Types
import GHC.Driver.Session
import GHC.Driver.Backend
import GHC.Driver.Ppr
+import GHC.Driver.Env
+
+import GHC.Tc.Types
+
import GHC.Core
import GHC.Core.Unfold
import GHC.Core.Unfold.Make
@@ -34,36 +37,47 @@ import GHC.Core.Rules
import GHC.Core.PatSyn
import GHC.Core.ConLike
import GHC.Core.Opt.Arity ( exprArity, exprBotStrictness_maybe )
+import GHC.Core.InstEnv
+import GHC.Core.Type ( tidyTopType )
+import GHC.Core.DataCon
+import GHC.Core.TyCon
+import GHC.Core.Class
+
import GHC.Iface.Tidy.StaticPtrTable
+import GHC.Iface.Env
+
+import GHC.Tc.Utils.Env
+import GHC.Tc.Utils.Monad
+
+import GHC.Utils.Outputable
+import GHC.Utils.Misc( filterOut )
+import GHC.Utils.Panic
+import qualified GHC.Utils.Error as Err
+
+import GHC.Types.ForeignStubs
import GHC.Types.Var.Env
import GHC.Types.Var.Set
import GHC.Types.Var
import GHC.Types.Id
import GHC.Types.Id.Make ( mkDictSelRhs )
import GHC.Types.Id.Info
-import GHC.Core.InstEnv
-import GHC.Core.Type ( tidyTopType )
import GHC.Types.Demand ( appIsDeadEnd, isTopSig, isDeadEndSig )
import GHC.Types.Cpr ( mkCprSig, botCpr )
import GHC.Types.Basic
import GHC.Types.Name hiding (varName)
import GHC.Types.Name.Set
import GHC.Types.Name.Cache
+import GHC.Types.Name.Ppr
import GHC.Types.Avail
-import GHC.Iface.Env
-import GHC.Tc.Utils.Env
-import GHC.Tc.Utils.Monad
-import GHC.Core.DataCon
-import GHC.Core.TyCon
-import GHC.Core.Class
+import GHC.Types.Unique.Supply
+import GHC.Types.TypeEnv
+
import GHC.Unit.Module
-import GHC.Driver.Types
+import GHC.Unit.Module.ModGuts
+import GHC.Unit.Module.ModDetails
+import GHC.Unit.Module.Deps
+
import GHC.Data.Maybe
-import GHC.Types.Unique.Supply
-import GHC.Utils.Outputable
-import GHC.Utils.Misc( filterOut )
-import GHC.Utils.Panic
-import qualified GHC.Utils.Error as Err
import Control.Monad
import Data.Function
diff --git a/compiler/GHC/Iface/Tidy/StaticPtrTable.hs b/compiler/GHC/Iface/Tidy/StaticPtrTable.hs
index b4a0a3c5a4..8f83e35333 100644
--- a/compiler/GHC/Iface/Tidy/StaticPtrTable.hs
+++ b/compiler/GHC/Iface/Tidy/StaticPtrTable.hs
@@ -124,23 +124,29 @@ Here is a running example:
-}
import GHC.Prelude
+import GHC.Platform
+
+import GHC.Driver.Session
+import GHC.Driver.Env
-import GHC.Cmm.CLabel
import GHC.Core
import GHC.Core.Utils (collectMakeStaticArgs)
import GHC.Core.DataCon
-import GHC.Driver.Session
-import GHC.Driver.Types
-import GHC.Types.Id
import GHC.Core.Make (mkStringExprFSWith)
+import GHC.Core.Type
+
+import GHC.Cmm.CLabel
+
import GHC.Unit.Module
-import GHC.Types.Name
import GHC.Utils.Outputable as Outputable
import GHC.Utils.Panic
-import GHC.Platform
import GHC.Builtin.Names
import GHC.Tc.Utils.Env (lookupGlobal)
-import GHC.Core.Type
+import GHC.Runtime.Linker.Types
+
+import GHC.Types.Name
+import GHC.Types.Id
+import GHC.Types.TyThing
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.State
diff --git a/compiler/GHC/Iface/Type.hs b/compiler/GHC/Iface/Type.hs
index 2e33770812..57889754fe 100644
--- a/compiler/GHC/Iface/Type.hs
+++ b/compiler/GHC/Iface/Type.hs
@@ -155,7 +155,7 @@ type IfaceKind = IfaceType
-- | A kind of universal type, used for types and kinds.
--
-- Any time a 'Type' is pretty-printed, it is first converted to an 'IfaceType'
--- before being printed. See Note [Pretty printing via Iface syntax] in "GHC.Core.Ppr.TyThing"
+-- before being printed. See Note [Pretty printing via Iface syntax] in "GHC.Types.TyThing.Ppr"
data IfaceType
= IfaceFreeTyVar TyVar -- See Note [Free tyvars in IfaceType]
| IfaceTyVar IfLclName -- Type/coercion variable only, not tycon
@@ -280,7 +280,7 @@ instance Outputable IfaceTyConSort where
Nowadays (since Nov 16, 2016) we pretty-print a Type by converting to
an IfaceType and pretty printing that. This eliminates a lot of
pretty-print duplication, and it matches what we do with pretty-
-printing TyThings. See Note [Pretty printing via Iface syntax] in GHC.Core.Ppr.TyThing.
+printing TyThings. See Note [Pretty printing via Iface syntax] in GHC.Types.TyThing.Ppr.
It works fine for closed types, but when printing debug traces (e.g.
when using -ddump-tc-trace) we print a lot of /open/ types. These
diff --git a/compiler/GHC/Iface/UpdateIdInfos.hs b/compiler/GHC/Iface/UpdateIdInfos.hs
index fcc93c110e..9c013cc320 100644
--- a/compiler/GHC/Iface/UpdateIdInfos.hs
+++ b/compiler/GHC/Iface/UpdateIdInfos.hs
@@ -8,13 +8,19 @@ import GHC.Prelude
import GHC.Core
import GHC.Core.InstEnv
-import GHC.Driver.Types
+
import GHC.StgToCmm.Types (CgInfos (..))
+
import GHC.Types.Id
import GHC.Types.Id.Info
import GHC.Types.Name.Env
import GHC.Types.Name.Set
import GHC.Types.Var
+import GHC.Types.TypeEnv
+import GHC.Types.TyThing
+
+import GHC.Unit.Module.ModDetails
+
import GHC.Utils.Misc
import GHC.Utils.Outputable
import GHC.Utils.Panic