summaryrefslogtreecommitdiff
path: root/compiler/GHC/Unit/Module
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/GHC/Unit/Module')
-rw-r--r--compiler/GHC/Unit/Module/Deps.hs195
-rw-r--r--compiler/GHC/Unit/Module/Graph.hs101
-rw-r--r--compiler/GHC/Unit/Module/Imported.hs54
-rw-r--r--compiler/GHC/Unit/Module/ModDetails.hs51
-rw-r--r--compiler/GHC/Unit/Module/ModGuts.hs140
-rw-r--r--compiler/GHC/Unit/Module/ModIface.hs537
-rw-r--r--compiler/GHC/Unit/Module/ModSummary.hs190
-rw-r--r--compiler/GHC/Unit/Module/Status.hs46
-rw-r--r--compiler/GHC/Unit/Module/Warnings.hs146
9 files changed, 1460 insertions, 0 deletions
diff --git a/compiler/GHC/Unit/Module/Deps.hs b/compiler/GHC/Unit/Module/Deps.hs
new file mode 100644
index 0000000000..5bdd23239b
--- /dev/null
+++ b/compiler/GHC/Unit/Module/Deps.hs
@@ -0,0 +1,195 @@
+-- | Dependencies and Usage of a module
+module GHC.Unit.Module.Deps
+ ( Dependencies (..)
+ , Usage (..)
+ , noDependencies
+ )
+where
+
+import GHC.Prelude
+
+import GHC.Types.SafeHaskell
+import GHC.Types.Name
+import GHC.Unit.Module.Name
+import GHC.Unit.Module
+
+import GHC.Utils.Fingerprint
+import GHC.Utils.Binary
+
+-- | Dependency information about ALL modules and packages below this one
+-- in the import hierarchy.
+--
+-- Invariant: the dependencies of a module @M@ never includes @M@.
+--
+-- Invariant: none of the lists contain duplicates.
+data Dependencies = Deps
+ { dep_mods :: [ModuleNameWithIsBoot]
+ -- ^ All home-package modules transitively below this one
+ -- I.e. modules that this one imports, or that are in the
+ -- dep_mods of those directly-imported modules
+
+ , dep_pkgs :: [(UnitId, Bool)]
+ -- ^ All packages transitively below this module
+ -- I.e. packages to which this module's direct imports belong,
+ -- or that are in the dep_pkgs of those modules
+ -- The bool indicates if the package is required to be
+ -- trusted when the module is imported as a safe import
+ -- (Safe Haskell). See Note [Tracking Trust Transitively] in GHC.Rename.Names
+
+ , dep_orphs :: [Module]
+ -- ^ Transitive closure of orphan modules (whether
+ -- home or external pkg).
+ --
+ -- (Possible optimization: don't include family
+ -- instance orphans as they are anyway included in
+ -- 'dep_finsts'. But then be careful about code
+ -- which relies on dep_orphs having the complete list!)
+ -- This does NOT include us, unlike 'imp_orphs'.
+
+ , dep_finsts :: [Module]
+ -- ^ Transitive closure of depended upon modules which
+ -- contain family instances (whether home or external).
+ -- This is used by 'checkFamInstConsistency'. This
+ -- does NOT include us, unlike 'imp_finsts'. See Note
+ -- [The type family instance consistency story].
+
+ , dep_plgins :: [ModuleName]
+ -- ^ All the plugins used while compiling this module.
+ }
+ deriving( Eq )
+ -- Equality used only for old/new comparison in GHC.Iface.Recomp.addFingerprints
+ -- See 'GHC.Tc.Utils.ImportAvails' for details on dependencies.
+
+instance Binary Dependencies where
+ put_ bh deps = do put_ bh (dep_mods deps)
+ put_ bh (dep_pkgs deps)
+ put_ bh (dep_orphs deps)
+ put_ bh (dep_finsts deps)
+ put_ bh (dep_plgins deps)
+
+ get bh = do ms <- get bh
+ ps <- get bh
+ os <- get bh
+ fis <- get bh
+ pl <- get bh
+ return (Deps { dep_mods = ms, dep_pkgs = ps, dep_orphs = os,
+ dep_finsts = fis, dep_plgins = pl })
+
+noDependencies :: Dependencies
+noDependencies = Deps [] [] [] [] []
+
+-- | Records modules for which changes may force recompilation of this module
+-- See wiki: https://gitlab.haskell.org/ghc/ghc/wikis/commentary/compiler/recompilation-avoidance
+--
+-- This differs from Dependencies. A module X may be in the dep_mods of this
+-- module (via an import chain) but if we don't use anything from X it won't
+-- appear in our Usage
+data Usage
+ -- | Module from another package
+ = UsagePackageModule {
+ usg_mod :: Module,
+ -- ^ External package module depended on
+ usg_mod_hash :: Fingerprint,
+ -- ^ Cached module fingerprint
+ usg_safe :: IsSafeImport
+ -- ^ Was this module imported as a safe import
+ }
+ -- | Module from the current package
+ | UsageHomeModule {
+ usg_mod_name :: ModuleName,
+ -- ^ Name of the module
+ usg_mod_hash :: Fingerprint,
+ -- ^ Cached module fingerprint
+ usg_entities :: [(OccName,Fingerprint)],
+ -- ^ Entities we depend on, sorted by occurrence name and fingerprinted.
+ -- NB: usages are for parent names only, e.g. type constructors
+ -- but not the associated data constructors.
+ usg_exports :: Maybe Fingerprint,
+ -- ^ Fingerprint for the export list of this module,
+ -- if we directly imported it (and hence we depend on its export list)
+ usg_safe :: IsSafeImport
+ -- ^ Was this module imported as a safe import
+ } -- ^ Module from the current package
+ -- | A file upon which the module depends, e.g. a CPP #include, or using TH's
+ -- 'addDependentFile'
+ | UsageFile {
+ usg_file_path :: FilePath,
+ -- ^ External file dependency. From a CPP #include or TH
+ -- addDependentFile. Should be absolute.
+ usg_file_hash :: Fingerprint
+ -- ^ 'Fingerprint' of the file contents.
+
+ -- Note: We don't consider things like modification timestamps
+ -- here, because there's no reason to recompile if the actual
+ -- contents don't change. This previously lead to odd
+ -- recompilation behaviors; see #8114
+ }
+ -- | A requirement which was merged into this one.
+ | UsageMergedRequirement {
+ usg_mod :: Module,
+ usg_mod_hash :: Fingerprint
+ }
+ deriving( Eq )
+ -- The export list field is (Just v) if we depend on the export list:
+ -- i.e. we imported the module directly, whether or not we
+ -- enumerated the things we imported, or just imported
+ -- everything
+ -- We need to recompile if M's exports change, because
+ -- if the import was import M, we might now have a name clash
+ -- in the importing module.
+ -- if the import was import M(x) M might no longer export x
+ -- The only way we don't depend on the export list is if we have
+ -- import M()
+ -- And of course, for modules that aren't imported directly we don't
+ -- depend on their export lists
+
+instance Binary Usage where
+ put_ bh usg@UsagePackageModule{} = do
+ putByte bh 0
+ put_ bh (usg_mod usg)
+ put_ bh (usg_mod_hash usg)
+ put_ bh (usg_safe usg)
+
+ put_ bh usg@UsageHomeModule{} = do
+ putByte bh 1
+ put_ bh (usg_mod_name usg)
+ put_ bh (usg_mod_hash usg)
+ put_ bh (usg_exports usg)
+ put_ bh (usg_entities usg)
+ put_ bh (usg_safe usg)
+
+ put_ bh usg@UsageFile{} = do
+ putByte bh 2
+ put_ bh (usg_file_path usg)
+ put_ bh (usg_file_hash usg)
+
+ put_ bh usg@UsageMergedRequirement{} = do
+ putByte bh 3
+ put_ bh (usg_mod usg)
+ put_ bh (usg_mod_hash usg)
+
+ get bh = do
+ h <- getByte bh
+ case h of
+ 0 -> do
+ nm <- get bh
+ mod <- get bh
+ safe <- get bh
+ return UsagePackageModule { usg_mod = nm, usg_mod_hash = mod, usg_safe = safe }
+ 1 -> do
+ nm <- get bh
+ mod <- get bh
+ exps <- get bh
+ ents <- get bh
+ safe <- get bh
+ return UsageHomeModule { usg_mod_name = nm, usg_mod_hash = mod,
+ usg_exports = exps, usg_entities = ents, usg_safe = safe }
+ 2 -> do
+ fp <- get bh
+ hash <- get bh
+ return UsageFile { usg_file_path = fp, usg_file_hash = hash }
+ 3 -> do
+ mod <- get bh
+ hash <- get bh
+ return UsageMergedRequirement { usg_mod = mod, usg_mod_hash = hash }
+ i -> error ("Binary.get(Usage): " ++ show i)
diff --git a/compiler/GHC/Unit/Module/Graph.hs b/compiler/GHC/Unit/Module/Graph.hs
new file mode 100644
index 0000000000..faa3ae9b1a
--- /dev/null
+++ b/compiler/GHC/Unit/Module/Graph.hs
@@ -0,0 +1,101 @@
+{-# LANGUAGE RecordWildCards #-}
+
+module GHC.Unit.Module.Graph
+ ( ModuleGraph
+ , emptyMG
+ , mkModuleGraph
+ , extendMG
+ , mapMG
+ , mgModSummaries
+ , mgElemModule
+ , mgLookupModule
+ , mgBootModules
+ , needsTemplateHaskellOrQQ
+ , isTemplateHaskellOrQQNonBoot
+ )
+where
+
+import GHC.Prelude
+
+import qualified GHC.LanguageExtensions as LangExt
+
+import GHC.Driver.Session
+
+import GHC.Unit.Module.ModSummary
+import GHC.Unit.Module.Env
+import GHC.Unit.Types
+
+
+-- | A ModuleGraph contains all the nodes from the home package (only).
+-- There will be a node for each source module, plus a node for each hi-boot
+-- module.
+--
+-- The graph is not necessarily stored in topologically-sorted order. Use
+-- 'GHC.topSortModuleGraph' and 'GHC.Data.Graph.Directed.flattenSCC' to achieve this.
+data ModuleGraph = ModuleGraph
+ { mg_mss :: [ModSummary]
+ , mg_non_boot :: ModuleEnv ModSummary
+ -- a map of all non-boot ModSummaries keyed by Modules
+ , mg_boot :: ModuleSet
+ -- a set of boot Modules
+ , mg_needs_th_or_qq :: !Bool
+ -- does any of the modules in mg_mss require TemplateHaskell or
+ -- QuasiQuotes?
+ }
+
+-- | Determines whether a set of modules requires Template Haskell or
+-- Quasi Quotes
+--
+-- Note that if the session's 'DynFlags' enabled Template Haskell when
+-- 'depanal' was called, then each module in the returned module graph will
+-- have Template Haskell enabled whether it is actually needed or not.
+needsTemplateHaskellOrQQ :: ModuleGraph -> Bool
+needsTemplateHaskellOrQQ mg = mg_needs_th_or_qq mg
+
+-- | Map a function 'f' over all the 'ModSummaries'.
+-- To preserve invariants 'f' can't change the isBoot status.
+mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph
+mapMG f mg@ModuleGraph{..} = mg
+ { mg_mss = map f mg_mss
+ , mg_non_boot = mapModuleEnv f mg_non_boot
+ }
+
+mgBootModules :: ModuleGraph -> ModuleSet
+mgBootModules ModuleGraph{..} = mg_boot
+
+mgModSummaries :: ModuleGraph -> [ModSummary]
+mgModSummaries = mg_mss
+
+mgElemModule :: ModuleGraph -> Module -> Bool
+mgElemModule ModuleGraph{..} m = elemModuleEnv m mg_non_boot
+
+-- | Look up a ModSummary in the ModuleGraph
+mgLookupModule :: ModuleGraph -> Module -> Maybe ModSummary
+mgLookupModule ModuleGraph{..} m = lookupModuleEnv mg_non_boot m
+
+emptyMG :: ModuleGraph
+emptyMG = ModuleGraph [] emptyModuleEnv emptyModuleSet False
+
+isTemplateHaskellOrQQNonBoot :: ModSummary -> Bool
+isTemplateHaskellOrQQNonBoot ms =
+ (xopt LangExt.TemplateHaskell (ms_hspp_opts ms)
+ || xopt LangExt.QuasiQuotes (ms_hspp_opts ms)) &&
+ (isBootSummary ms == NotBoot)
+
+-- | Add a ModSummary to ModuleGraph. Assumes that the new ModSummary is
+-- not an element of the ModuleGraph.
+extendMG :: ModuleGraph -> ModSummary -> ModuleGraph
+extendMG ModuleGraph{..} ms = ModuleGraph
+ { mg_mss = ms:mg_mss
+ , mg_non_boot = case isBootSummary ms of
+ IsBoot -> mg_non_boot
+ NotBoot -> extendModuleEnv mg_non_boot (ms_mod ms) ms
+ , mg_boot = case isBootSummary ms of
+ NotBoot -> mg_boot
+ IsBoot -> extendModuleSet mg_boot (ms_mod ms)
+ , mg_needs_th_or_qq = mg_needs_th_or_qq || isTemplateHaskellOrQQNonBoot ms
+ }
+
+mkModuleGraph :: [ModSummary] -> ModuleGraph
+mkModuleGraph = foldr (flip extendMG) emptyMG
+
diff --git a/compiler/GHC/Unit/Module/Imported.hs b/compiler/GHC/Unit/Module/Imported.hs
new file mode 100644
index 0000000000..d6cd3ac88f
--- /dev/null
+++ b/compiler/GHC/Unit/Module/Imported.hs
@@ -0,0 +1,54 @@
+module GHC.Unit.Module.Imported
+ ( ImportedMods
+ , ImportedBy (..)
+ , ImportedModsVal (..)
+ , importedByUser
+ )
+where
+
+import GHC.Prelude
+
+import GHC.Unit.Module
+
+import GHC.Types.Name.Reader
+import GHC.Types.SafeHaskell
+import GHC.Types.SrcLoc
+
+-- | Records the modules directly imported by a module for extracting e.g.
+-- usage information, and also to give better error message
+type ImportedMods = ModuleEnv [ImportedBy]
+
+-- | If a module was "imported" by the user, we associate it with
+-- more detailed usage information 'ImportedModsVal'; a module
+-- imported by the system only gets used for usage information.
+data ImportedBy
+ = ImportedByUser ImportedModsVal
+ | ImportedBySystem
+
+importedByUser :: [ImportedBy] -> [ImportedModsVal]
+importedByUser (ImportedByUser imv : bys) = imv : importedByUser bys
+importedByUser (ImportedBySystem : bys) = importedByUser bys
+importedByUser [] = []
+
+data ImportedModsVal = ImportedModsVal
+ { imv_name :: ModuleName
+ -- ^ The name the module is imported with
+
+ , imv_span :: SrcSpan
+ -- ^ the source span of the whole import
+
+ , imv_is_safe :: IsSafeImport
+ -- ^ whether this is a safe import
+
+ , imv_is_hiding :: Bool
+ -- ^ whether this is an "hiding" import
+
+ , imv_all_exports :: !GlobalRdrEnv
+ -- ^ all the things the module could provide.
+ --
+ -- NB. BangPattern here: otherwise this leaks. (#15111)
+
+ , imv_qualified :: Bool
+ -- ^ whether this is a qualified import
+ }
+
diff --git a/compiler/GHC/Unit/Module/ModDetails.hs b/compiler/GHC/Unit/Module/ModDetails.hs
new file mode 100644
index 0000000000..31b3bdb9a0
--- /dev/null
+++ b/compiler/GHC/Unit/Module/ModDetails.hs
@@ -0,0 +1,51 @@
+module GHC.Unit.Module.ModDetails
+ ( ModDetails (..)
+ , emptyModDetails
+ )
+where
+
+import GHC.Core ( CoreRule )
+import GHC.Core.FamInstEnv
+import GHC.Core.InstEnv ( ClsInst )
+
+import GHC.Types.Avail
+import GHC.Types.CompleteMatch
+import GHC.Types.TypeEnv
+import GHC.Types.Annotations ( Annotation )
+
+-- | The 'ModDetails' is essentially a cache for information in the 'ModIface'
+-- for home modules only. Information relating to packages will be loaded into
+-- global environments in 'ExternalPackageState'.
+data ModDetails = ModDetails
+ { -- The next two fields are created by the typechecker
+ md_exports :: [AvailInfo]
+ , md_types :: !TypeEnv
+ -- ^ Local type environment for this particular module
+ -- Includes Ids, TyCons, PatSyns
+
+ , md_insts :: ![ClsInst]
+ -- ^ 'DFunId's for the instances in this module
+
+ , md_fam_insts :: ![FamInst]
+ , md_rules :: ![CoreRule]
+ -- ^ Domain may include 'Id's from other modules
+
+ , md_anns :: ![Annotation]
+ -- ^ Annotations present in this module: currently
+ -- they only annotate things also declared in this module
+
+ , md_complete_matches :: [CompleteMatch]
+ -- ^ Complete match pragmas for this module
+ }
+
+-- | Constructs an empty ModDetails
+emptyModDetails :: ModDetails
+emptyModDetails = ModDetails
+ { md_types = emptyTypeEnv
+ , md_exports = []
+ , md_insts = []
+ , md_rules = []
+ , md_fam_insts = []
+ , md_anns = []
+ , md_complete_matches = []
+ }
diff --git a/compiler/GHC/Unit/Module/ModGuts.hs b/compiler/GHC/Unit/Module/ModGuts.hs
new file mode 100644
index 0000000000..4b75dff099
--- /dev/null
+++ b/compiler/GHC/Unit/Module/ModGuts.hs
@@ -0,0 +1,140 @@
+module GHC.Unit.Module.ModGuts
+ ( ModGuts (..)
+ , CgGuts (..)
+ )
+where
+
+import GHC.Prelude
+
+import GHC.ByteCode.Types
+import GHC.ForeignSrcLang
+
+import GHC.Hs
+
+import GHC.Unit
+import GHC.Unit.Module.Deps
+import GHC.Unit.Module.Warnings
+
+import GHC.Core.InstEnv ( InstEnv, ClsInst )
+import GHC.Core.FamInstEnv
+import GHC.Core ( CoreProgram, CoreRule )
+import GHC.Core.TyCon
+import GHC.Core.PatSyn
+
+import GHC.Runtime.Linker.Types ( SptEntry(..) )
+
+import GHC.Types.Annotations ( Annotation )
+import GHC.Types.Avail
+import GHC.Types.CompleteMatch
+import GHC.Types.Fixity.Env
+import GHC.Types.ForeignStubs
+import GHC.Types.HpcInfo
+import GHC.Types.Name.Reader
+import GHC.Types.SafeHaskell
+import GHC.Types.SourceFile ( HscSource(..) )
+import GHC.Types.SrcLoc
+
+
+-- | A ModGuts is carried through the compiler, accumulating stuff as it goes
+-- There is only one ModGuts at any time, the one for the module
+-- being compiled right now. Once it is compiled, a 'ModIface' and
+-- 'ModDetails' are extracted and the ModGuts is discarded.
+data ModGuts
+ = ModGuts {
+ mg_module :: !Module, -- ^ Module being compiled
+ mg_hsc_src :: HscSource, -- ^ Whether it's an hs-boot module
+ mg_loc :: SrcSpan, -- ^ For error messages from inner passes
+ mg_exports :: ![AvailInfo], -- ^ What it exports
+ mg_deps :: !Dependencies, -- ^ What it depends on, directly or
+ -- otherwise
+ mg_usages :: ![Usage], -- ^ What was used? Used for interfaces.
+
+ mg_used_th :: !Bool, -- ^ Did we run a TH splice?
+ mg_rdr_env :: !GlobalRdrEnv, -- ^ Top-level lexical environment
+
+ -- These fields all describe the things **declared in this module**
+ mg_fix_env :: !FixityEnv, -- ^ Fixities declared in this module.
+ -- Used for creating interface files.
+ mg_tcs :: ![TyCon], -- ^ TyCons declared in this module
+ -- (includes TyCons for classes)
+ mg_insts :: ![ClsInst], -- ^ Class instances declared in this module
+ mg_fam_insts :: ![FamInst],
+ -- ^ Family instances declared in this module
+ mg_patsyns :: ![PatSyn], -- ^ Pattern synonyms declared in this module
+ mg_rules :: ![CoreRule], -- ^ Before the core pipeline starts, contains
+ -- See Note [Overall plumbing for rules] in "GHC.Core.Rules"
+ mg_binds :: !CoreProgram, -- ^ Bindings for this module
+ mg_foreign :: !ForeignStubs, -- ^ Foreign exports declared in this module
+ mg_foreign_files :: ![(ForeignSrcLang, FilePath)],
+ -- ^ Files to be compiled with the C compiler
+ mg_warns :: !Warnings, -- ^ Warnings declared in the module
+ mg_anns :: [Annotation], -- ^ Annotations declared in this module
+ mg_complete_matches :: [CompleteMatch], -- ^ Complete Matches
+ mg_hpc_info :: !HpcInfo, -- ^ Coverage tick boxes in the module
+ mg_modBreaks :: !(Maybe ModBreaks), -- ^ Breakpoints for the module
+
+ -- The next two fields are unusual, because they give instance
+ -- environments for *all* modules in the home package, including
+ -- this module, rather than for *just* this module.
+ -- Reason: when looking up an instance we don't want to have to
+ -- look at each module in the home package in turn
+ mg_inst_env :: InstEnv, -- ^ Class instance environment for
+ -- /home-package/ modules (including this
+ -- one); c.f. 'tcg_inst_env'
+ mg_fam_inst_env :: FamInstEnv, -- ^ Type-family instance environment for
+ -- /home-package/ modules (including this
+ -- one); c.f. 'tcg_fam_inst_env'
+
+ mg_safe_haskell :: SafeHaskellMode, -- ^ Safe Haskell mode
+ mg_trust_pkg :: Bool, -- ^ Do we need to trust our
+ -- own package for Safe Haskell?
+ -- See Note [Trust Own Package]
+ -- in "GHC.Rename.Names"
+
+ mg_doc_hdr :: !(Maybe HsDocString), -- ^ Module header.
+ mg_decl_docs :: !DeclDocMap, -- ^ Docs on declarations.
+ mg_arg_docs :: !ArgDocMap -- ^ Docs on arguments.
+ }
+
+-- The ModGuts takes on several slightly different forms:
+--
+-- After simplification, the following fields change slightly:
+-- mg_rules Orphan rules only (local ones now attached to binds)
+-- mg_binds With rules attached
+
+---------------------------------------------------------
+-- The Tidy pass forks the information about this module:
+-- * one lot goes to interface file generation (ModIface)
+-- and later compilations (ModDetails)
+-- * the other lot goes to code generation (CgGuts)
+
+-- | A restricted form of 'ModGuts' for code generation purposes
+data CgGuts
+ = CgGuts {
+ cg_module :: !Module,
+ -- ^ Module being compiled
+
+ cg_tycons :: [TyCon],
+ -- ^ Algebraic data types (including ones that started
+ -- life as classes); generate constructors and info
+ -- tables. Includes newtypes, just for the benefit of
+ -- External Core
+
+ cg_binds :: CoreProgram,
+ -- ^ The tidied main bindings, including
+ -- previously-implicit bindings for record and class
+ -- selectors, and data constructor wrappers. But *not*
+ -- data constructor workers; reason: we regard them
+ -- as part of the code-gen of tycons
+
+ cg_foreign :: !ForeignStubs, -- ^ Foreign export stubs
+ cg_foreign_files :: ![(ForeignSrcLang, FilePath)],
+ cg_dep_pkgs :: ![UnitId], -- ^ Dependent packages, used to
+ -- generate #includes for C code gen
+ cg_hpc_info :: !HpcInfo, -- ^ Program coverage tick box information
+ cg_modBreaks :: !(Maybe ModBreaks), -- ^ Module breakpoints
+ cg_spt_entries :: [SptEntry]
+ -- ^ Static pointer table entries for static forms defined in
+ -- the module.
+ -- See Note [Grand plan for static forms] in "GHC.Iface.Tidy.StaticPtrTable"
+ }
diff --git a/compiler/GHC/Unit/Module/ModIface.hs b/compiler/GHC/Unit/Module/ModIface.hs
new file mode 100644
index 0000000000..83bc565b6f
--- /dev/null
+++ b/compiler/GHC/Unit/Module/ModIface.hs
@@ -0,0 +1,537 @@
+{-# LANGUAGE KindSignatures #-}
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE TypeSynonymInstances #-}
+{-# LANGUAGE UndecidableInstances #-}
+
+module GHC.Unit.Module.ModIface
+ ( ModIface
+ , ModIface_ (..)
+ , PartialModIface
+ , ModIfaceBackend (..)
+ , IfaceDeclExts
+ , IfaceBackendExts
+ , IfaceExport
+ , WhetherHasOrphans
+ , WhetherHasFamInst
+ , mi_boot
+ , mi_fix
+ , mi_semantic_module
+ , mi_free_holes
+ , renameFreeHoles
+ , emptyPartialModIface
+ , emptyFullModIface
+ , mkIfaceHashCache
+ , emptyIfaceHashCache
+ )
+where
+
+import GHC.Prelude
+
+import GHC.Hs
+
+import GHC.Iface.Syntax
+import GHC.Iface.Ext.Fields
+
+import GHC.Unit
+import GHC.Unit.Module.Deps
+import GHC.Unit.Module.Warnings
+
+import GHC.Types.Avail
+import GHC.Types.Fixity
+import GHC.Types.Fixity.Env
+import GHC.Types.HpcInfo
+import GHC.Types.Name
+import GHC.Types.Name.Reader
+import GHC.Types.SafeHaskell
+import GHC.Types.SourceFile
+import GHC.Types.Unique.DSet
+import GHC.Types.Unique.FM
+
+import GHC.Data.Maybe
+
+import GHC.Utils.Fingerprint
+import GHC.Utils.Binary
+
+import Control.DeepSeq
+
+{- Note [Interface file stages]
+ ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+Interface files have two possible stages.
+
+* A partial stage built from the result of the core pipeline.
+* A fully instantiated form. Which also includes fingerprints and
+ potentially information provided by backends.
+
+We can build a full interface file two ways:
+* Directly from a partial one:
+ Then we omit backend information and mostly compute fingerprints.
+* From a partial one + information produced by a backend.
+ Then we store the provided information and fingerprint both.
+-}
+
+type PartialModIface = ModIface_ 'ModIfaceCore
+type ModIface = ModIface_ 'ModIfaceFinal
+
+-- | Extends a PartialModIface with information which is either:
+-- * Computed after codegen
+-- * Or computed just before writing the iface to disk. (Hashes)
+-- In order to fully instantiate it.
+data ModIfaceBackend = ModIfaceBackend
+ { mi_iface_hash :: !Fingerprint
+ -- ^ Hash of the whole interface
+ , mi_mod_hash :: !Fingerprint
+ -- ^ Hash of the ABI only
+ , mi_flag_hash :: !Fingerprint
+ -- ^ Hash of the important flags used when compiling the module, excluding
+ -- optimisation flags
+ , mi_opt_hash :: !Fingerprint
+ -- ^ Hash of optimisation flags
+ , mi_hpc_hash :: !Fingerprint
+ -- ^ Hash of hpc flags
+ , mi_plugin_hash :: !Fingerprint
+ -- ^ Hash of plugins
+ , mi_orphan :: !WhetherHasOrphans
+ -- ^ Whether this module has orphans
+ , mi_finsts :: !WhetherHasFamInst
+ -- ^ Whether this module has family instances. See Note [The type family
+ -- instance consistency story].
+ , mi_exp_hash :: !Fingerprint
+ -- ^ Hash of export list
+ , mi_orphan_hash :: !Fingerprint
+ -- ^ Hash for orphan rules, class and family instances combined
+
+ -- Cached environments for easy lookup. These are computed (lazily) from
+ -- other fields and are not put into the interface file.
+ -- Not really produced by the backend but there is no need to create them
+ -- any earlier.
+ , mi_warn_fn :: !(OccName -> Maybe WarningTxt)
+ -- ^ Cached lookup for 'mi_warns'
+ , mi_fix_fn :: !(OccName -> Maybe Fixity)
+ -- ^ Cached lookup for 'mi_fixities'
+ , mi_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint))
+ -- ^ Cached lookup for 'mi_decls'. The @Nothing@ in 'mi_hash_fn' means that
+ -- the thing isn't in decls. It's useful to know that when seeing if we are
+ -- up to date wrt. the old interface. The 'OccName' is the parent of the
+ -- name, if it has one.
+ }
+
+data ModIfacePhase
+ = ModIfaceCore
+ -- ^ Partial interface built based on output of core pipeline.
+ | ModIfaceFinal
+
+-- | Selects a IfaceDecl representation.
+-- For fully instantiated interfaces we also maintain
+-- a fingerprint, which is used for recompilation checks.
+type family IfaceDeclExts (phase :: ModIfacePhase) where
+ IfaceDeclExts 'ModIfaceCore = IfaceDecl
+ IfaceDeclExts 'ModIfaceFinal = (Fingerprint, IfaceDecl)
+
+type family IfaceBackendExts (phase :: ModIfacePhase) where
+ IfaceBackendExts 'ModIfaceCore = ()
+ IfaceBackendExts 'ModIfaceFinal = ModIfaceBackend
+
+
+
+-- | A 'ModIface' plus a 'ModDetails' summarises everything we know
+-- about a compiled module. The 'ModIface' is the stuff *before* linking,
+-- and can be written out to an interface file. The 'ModDetails is after
+-- linking and can be completely recovered from just the 'ModIface'.
+--
+-- When we read an interface file, we also construct a 'ModIface' from it,
+-- except that we explicitly make the 'mi_decls' and a few other fields empty;
+-- as when reading we consolidate the declarations etc. into a number of indexed
+-- maps and environments in the 'ExternalPackageState'.
+data ModIface_ (phase :: ModIfacePhase)
+ = ModIface {
+ mi_module :: !Module, -- ^ Name of the module we are for
+ mi_sig_of :: !(Maybe Module), -- ^ Are we a sig of another mod?
+
+ mi_hsc_src :: !HscSource, -- ^ Boot? Signature?
+
+ mi_deps :: Dependencies,
+ -- ^ The dependencies of the module. This is
+ -- consulted for directly-imported modules, but not
+ -- for anything else (hence lazy)
+
+ mi_usages :: [Usage],
+ -- ^ Usages; kept sorted so that it's easy to decide
+ -- whether to write a new iface file (changing usages
+ -- doesn't affect the hash of this module)
+ -- NOT STRICT! we read this field lazily from the interface file
+ -- It is *only* consulted by the recompilation checker
+
+ mi_exports :: ![IfaceExport],
+ -- ^ Exports
+ -- Kept sorted by (mod,occ), to make version comparisons easier
+ -- Records the modules that are the declaration points for things
+ -- exported by this module, and the 'OccName's of those things
+
+
+ mi_used_th :: !Bool,
+ -- ^ Module required TH splices when it was compiled.
+ -- This disables recompilation avoidance (see #481).
+
+ mi_fixities :: [(OccName,Fixity)],
+ -- ^ Fixities
+ -- NOT STRICT! we read this field lazily from the interface file
+
+ mi_warns :: Warnings,
+ -- ^ Warnings
+ -- NOT STRICT! we read this field lazily from the interface file
+
+ mi_anns :: [IfaceAnnotation],
+ -- ^ Annotations
+ -- NOT STRICT! we read this field lazily from the interface file
+
+
+ mi_decls :: [IfaceDeclExts phase],
+ -- ^ Type, class and variable declarations
+ -- The hash of an Id changes if its fixity or deprecations change
+ -- (as well as its type of course)
+ -- Ditto data constructors, class operations, except that
+ -- the hash of the parent class/tycon changes
+
+ mi_globals :: !(Maybe GlobalRdrEnv),
+ -- ^ Binds all the things defined at the top level in
+ -- the /original source/ code for this module. which
+ -- is NOT the same as mi_exports, nor mi_decls (which
+ -- may contains declarations for things not actually
+ -- defined by the user). Used for GHCi and for inspecting
+ -- the contents of modules via the GHC API only.
+ --
+ -- (We need the source file to figure out the
+ -- top-level environment, if we didn't compile this module
+ -- from source then this field contains @Nothing@).
+ --
+ -- Strictly speaking this field should live in the
+ -- 'HomeModInfo', but that leads to more plumbing.
+
+ -- Instance declarations and rules
+ mi_insts :: [IfaceClsInst], -- ^ Sorted class instance
+ mi_fam_insts :: [IfaceFamInst], -- ^ Sorted family instances
+ mi_rules :: [IfaceRule], -- ^ Sorted rules
+
+ mi_hpc :: !AnyHpcUsage,
+ -- ^ True if this program uses Hpc at any point in the program.
+
+ mi_trust :: !IfaceTrustInfo,
+ -- ^ Safe Haskell Trust information for this module.
+
+ mi_trust_pkg :: !Bool,
+ -- ^ Do we require the package this module resides in be trusted
+ -- to trust this module? This is used for the situation where a
+ -- module is Safe (so doesn't require the package be trusted
+ -- itself) but imports some trustworthy modules from its own
+ -- package (which does require its own package be trusted).
+ -- See Note [Trust Own Package] in GHC.Rename.Names
+ mi_complete_matches :: [IfaceCompleteMatch],
+
+ mi_doc_hdr :: Maybe HsDocString,
+ -- ^ Module header.
+
+ mi_decl_docs :: DeclDocMap,
+ -- ^ Docs on declarations.
+
+ mi_arg_docs :: ArgDocMap,
+ -- ^ Docs on arguments.
+
+ mi_final_exts :: !(IfaceBackendExts phase),
+ -- ^ Either `()` or `ModIfaceBackend` for
+ -- a fully instantiated interface.
+
+ mi_ext_fields :: ExtensibleFields
+ -- ^ Additional optional fields, where the Map key represents
+ -- the field name, resulting in a (size, serialized data) pair.
+ -- Because the data is intended to be serialized through the
+ -- internal `Binary` class (increasing compatibility with types
+ -- using `Name` and `FastString`, such as HIE), this format is
+ -- chosen over `ByteString`s.
+ }
+
+-- | Old-style accessor for whether or not the ModIface came from an hs-boot
+-- file.
+mi_boot :: ModIface -> IsBootInterface
+mi_boot iface = if mi_hsc_src iface == HsBootFile
+ then IsBoot
+ else NotBoot
+
+-- | Lookups up a (possibly cached) fixity from a 'ModIface'. If one cannot be
+-- found, 'defaultFixity' is returned instead.
+mi_fix :: ModIface -> OccName -> Fixity
+mi_fix iface name = mi_fix_fn (mi_final_exts iface) name `orElse` defaultFixity
+
+-- | The semantic module for this interface; e.g., if it's a interface
+-- for a signature, if 'mi_module' is @p[A=<A>]:A@, 'mi_semantic_module'
+-- will be @<A>@.
+mi_semantic_module :: ModIface_ a -> Module
+mi_semantic_module iface = case mi_sig_of iface of
+ Nothing -> mi_module iface
+ Just mod -> mod
+
+-- | The "precise" free holes, e.g., the signatures that this
+-- 'ModIface' depends on.
+mi_free_holes :: ModIface -> UniqDSet ModuleName
+mi_free_holes iface =
+ case getModuleInstantiation (mi_module iface) of
+ (_, Just indef)
+ -- A mini-hack: we rely on the fact that 'renameFreeHoles'
+ -- drops things that aren't holes.
+ -> renameFreeHoles (mkUniqDSet cands) (instUnitInsts (moduleUnit indef))
+ _ -> emptyUniqDSet
+ where
+ cands = map gwib_mod $ dep_mods $ mi_deps iface
+
+-- | Given a set of free holes, and a unit identifier, rename
+-- the free holes according to the instantiation of the unit
+-- identifier. For example, if we have A and B free, and
+-- our unit identity is @p[A=<C>,B=impl:B]@, the renamed free
+-- holes are just C.
+renameFreeHoles :: UniqDSet ModuleName -> [(ModuleName, Module)] -> UniqDSet ModuleName
+renameFreeHoles fhs insts =
+ unionManyUniqDSets (map lookup_impl (uniqDSetToList fhs))
+ where
+ hmap = listToUFM insts
+ lookup_impl mod_name
+ | Just mod <- lookupUFM hmap mod_name = moduleFreeHoles mod
+ -- It wasn't actually a hole
+ | otherwise = emptyUniqDSet
+
+
+instance Binary ModIface where
+ put_ bh (ModIface {
+ mi_module = mod,
+ mi_sig_of = sig_of,
+ mi_hsc_src = hsc_src,
+ mi_deps = deps,
+ mi_usages = usages,
+ mi_exports = exports,
+ mi_used_th = used_th,
+ mi_fixities = fixities,
+ mi_warns = warns,
+ mi_anns = anns,
+ mi_decls = decls,
+ mi_insts = insts,
+ mi_fam_insts = fam_insts,
+ mi_rules = rules,
+ mi_hpc = hpc_info,
+ mi_trust = trust,
+ mi_trust_pkg = trust_pkg,
+ mi_complete_matches = complete_matches,
+ mi_doc_hdr = doc_hdr,
+ mi_decl_docs = decl_docs,
+ mi_arg_docs = arg_docs,
+ mi_ext_fields = _ext_fields, -- Don't `put_` this in the instance so we
+ -- can deal with it's pointer in the header
+ -- when we write the actual file
+ mi_final_exts = ModIfaceBackend {
+ mi_iface_hash = iface_hash,
+ mi_mod_hash = mod_hash,
+ mi_flag_hash = flag_hash,
+ mi_opt_hash = opt_hash,
+ mi_hpc_hash = hpc_hash,
+ mi_plugin_hash = plugin_hash,
+ mi_orphan = orphan,
+ mi_finsts = hasFamInsts,
+ mi_exp_hash = exp_hash,
+ mi_orphan_hash = orphan_hash
+ }}) = do
+ put_ bh mod
+ put_ bh sig_of
+ put_ bh hsc_src
+ put_ bh iface_hash
+ put_ bh mod_hash
+ put_ bh flag_hash
+ put_ bh opt_hash
+ put_ bh hpc_hash
+ put_ bh plugin_hash
+ put_ bh orphan
+ put_ bh hasFamInsts
+ lazyPut bh deps
+ lazyPut bh usages
+ put_ bh exports
+ put_ bh exp_hash
+ put_ bh used_th
+ put_ bh fixities
+ lazyPut bh warns
+ lazyPut bh anns
+ put_ bh decls
+ put_ bh insts
+ put_ bh fam_insts
+ lazyPut bh rules
+ put_ bh orphan_hash
+ put_ bh hpc_info
+ put_ bh trust
+ put_ bh trust_pkg
+ put_ bh complete_matches
+ lazyPut bh doc_hdr
+ lazyPut bh decl_docs
+ lazyPut bh arg_docs
+
+ get bh = do
+ mod <- get bh
+ sig_of <- get bh
+ hsc_src <- get bh
+ iface_hash <- get bh
+ mod_hash <- get bh
+ flag_hash <- get bh
+ opt_hash <- get bh
+ hpc_hash <- get bh
+ plugin_hash <- get bh
+ orphan <- get bh
+ hasFamInsts <- get bh
+ deps <- lazyGet bh
+ usages <- {-# SCC "bin_usages" #-} lazyGet bh
+ exports <- {-# SCC "bin_exports" #-} get bh
+ exp_hash <- get bh
+ used_th <- get bh
+ fixities <- {-# SCC "bin_fixities" #-} get bh
+ warns <- {-# SCC "bin_warns" #-} lazyGet bh
+ anns <- {-# SCC "bin_anns" #-} lazyGet bh
+ decls <- {-# SCC "bin_tycldecls" #-} get bh
+ insts <- {-# SCC "bin_insts" #-} get bh
+ fam_insts <- {-# SCC "bin_fam_insts" #-} get bh
+ rules <- {-# SCC "bin_rules" #-} lazyGet bh
+ orphan_hash <- get bh
+ hpc_info <- get bh
+ trust <- get bh
+ trust_pkg <- get bh
+ complete_matches <- get bh
+ doc_hdr <- lazyGet bh
+ decl_docs <- lazyGet bh
+ arg_docs <- lazyGet bh
+ return (ModIface {
+ mi_module = mod,
+ mi_sig_of = sig_of,
+ mi_hsc_src = hsc_src,
+ mi_deps = deps,
+ mi_usages = usages,
+ mi_exports = exports,
+ mi_used_th = used_th,
+ mi_anns = anns,
+ mi_fixities = fixities,
+ mi_warns = warns,
+ mi_decls = decls,
+ mi_globals = Nothing,
+ mi_insts = insts,
+ mi_fam_insts = fam_insts,
+ mi_rules = rules,
+ mi_hpc = hpc_info,
+ mi_trust = trust,
+ mi_trust_pkg = trust_pkg,
+ -- And build the cached values
+ mi_complete_matches = complete_matches,
+ mi_doc_hdr = doc_hdr,
+ mi_decl_docs = decl_docs,
+ mi_arg_docs = arg_docs,
+ mi_ext_fields = emptyExtensibleFields, -- placeholder because this is dealt
+ -- with specially when the file is read
+ mi_final_exts = ModIfaceBackend {
+ mi_iface_hash = iface_hash,
+ mi_mod_hash = mod_hash,
+ mi_flag_hash = flag_hash,
+ mi_opt_hash = opt_hash,
+ mi_hpc_hash = hpc_hash,
+ mi_plugin_hash = plugin_hash,
+ mi_orphan = orphan,
+ mi_finsts = hasFamInsts,
+ mi_exp_hash = exp_hash,
+ mi_orphan_hash = orphan_hash,
+ mi_warn_fn = mkIfaceWarnCache warns,
+ mi_fix_fn = mkIfaceFixCache fixities,
+ mi_hash_fn = mkIfaceHashCache decls
+ }})
+
+-- | The original names declared of a certain module that are exported
+type IfaceExport = AvailInfo
+
+emptyPartialModIface :: Module -> PartialModIface
+emptyPartialModIface mod
+ = ModIface { mi_module = mod,
+ mi_sig_of = Nothing,
+ mi_hsc_src = HsSrcFile,
+ mi_deps = noDependencies,
+ mi_usages = [],
+ mi_exports = [],
+ mi_used_th = False,
+ mi_fixities = [],
+ mi_warns = NoWarnings,
+ mi_anns = [],
+ mi_insts = [],
+ mi_fam_insts = [],
+ mi_rules = [],
+ mi_decls = [],
+ mi_globals = Nothing,
+ mi_hpc = False,
+ mi_trust = noIfaceTrustInfo,
+ mi_trust_pkg = False,
+ mi_complete_matches = [],
+ mi_doc_hdr = Nothing,
+ mi_decl_docs = emptyDeclDocMap,
+ mi_arg_docs = emptyArgDocMap,
+ mi_final_exts = (),
+ mi_ext_fields = emptyExtensibleFields
+ }
+
+emptyFullModIface :: Module -> ModIface
+emptyFullModIface mod =
+ (emptyPartialModIface mod)
+ { mi_decls = []
+ , mi_final_exts = ModIfaceBackend
+ { mi_iface_hash = fingerprint0,
+ mi_mod_hash = fingerprint0,
+ mi_flag_hash = fingerprint0,
+ mi_opt_hash = fingerprint0,
+ mi_hpc_hash = fingerprint0,
+ mi_plugin_hash = fingerprint0,
+ mi_orphan = False,
+ mi_finsts = False,
+ mi_exp_hash = fingerprint0,
+ mi_orphan_hash = fingerprint0,
+ mi_warn_fn = emptyIfaceWarnCache,
+ mi_fix_fn = emptyIfaceFixCache,
+ mi_hash_fn = emptyIfaceHashCache } }
+
+-- | Constructs cache for the 'mi_hash_fn' field of a 'ModIface'
+mkIfaceHashCache :: [(Fingerprint,IfaceDecl)]
+ -> (OccName -> Maybe (OccName, Fingerprint))
+mkIfaceHashCache pairs
+ = \occ -> lookupOccEnv env occ
+ where
+ env = foldl' add_decl emptyOccEnv pairs
+ add_decl env0 (v,d) = foldl' add env0 (ifaceDeclFingerprints v d)
+ where
+ add env0 (occ,hash) = extendOccEnv env0 occ (occ,hash)
+
+emptyIfaceHashCache :: OccName -> Maybe (OccName, Fingerprint)
+emptyIfaceHashCache _occ = Nothing
+
+-- Take care, this instance only forces to the degree necessary to
+-- avoid major space leaks.
+instance (NFData (IfaceBackendExts (phase :: ModIfacePhase)), NFData (IfaceDeclExts (phase :: ModIfacePhase))) => NFData (ModIface_ phase) where
+ rnf (ModIface f1 f2 f3 f4 f5 f6 f7 f8 f9 f10 f11 f12
+ f13 f14 f15 f16 f17 f18 f19 f20 f21 f22 f23 f24) =
+ rnf f1 `seq` rnf f2 `seq` f3 `seq` f4 `seq` f5 `seq` f6 `seq` rnf f7 `seq` f8 `seq`
+ f9 `seq` rnf f10 `seq` rnf f11 `seq` f12 `seq` rnf f13 `seq` rnf f14 `seq` rnf f15 `seq`
+ rnf f16 `seq` f17 `seq` rnf f18 `seq` rnf f19 `seq` f20 `seq` f21 `seq` f22 `seq` rnf f23
+ `seq` rnf f24
+
+-- | Records whether a module has orphans. An \"orphan\" is one of:
+--
+-- * An instance declaration in a module other than the definition
+-- module for one of the type constructors or classes in the instance head
+--
+-- * A rewrite rule in a module other than the one defining
+-- the function in the head of the rule
+--
+type WhetherHasOrphans = Bool
+
+-- | Does this module define family instances?
+type WhetherHasFamInst = Bool
+
+
+
diff --git a/compiler/GHC/Unit/Module/ModSummary.hs b/compiler/GHC/Unit/Module/ModSummary.hs
new file mode 100644
index 0000000000..a0b42fc2a4
--- /dev/null
+++ b/compiler/GHC/Unit/Module/ModSummary.hs
@@ -0,0 +1,190 @@
+-- | A ModSummary is a node in the compilation manager's dependency graph
+-- (ModuleGraph)
+module GHC.Unit.Module.ModSummary
+ ( ModSummary (..)
+ , ms_installed_mod
+ , ms_mod_name
+ , ms_imps
+ , ms_home_allimps
+ , ms_home_srcimps
+ , ms_home_imps
+ , msHiFilePath
+ , msHsFilePath
+ , msObjFilePath
+ , msDynObjFilePath
+ , isBootSummary
+ , showModMsg
+ , findTarget
+ )
+where
+
+import GHC.Prelude
+
+import GHC.Hs
+
+import GHC.Driver.Ppr
+import GHC.Driver.Session
+import GHC.Driver.Backend
+
+import GHC.Unit.Types
+import GHC.Unit.Module
+
+import GHC.Types.SourceFile ( HscSource(..), hscSourceString )
+import GHC.Types.SrcLoc
+import GHC.Types.Target
+
+import GHC.Data.Maybe
+import GHC.Data.FastString
+import GHC.Data.StringBuffer ( StringBuffer )
+
+import GHC.Utils.Outputable
+
+import Data.Time
+import System.FilePath
+
+-- | A single node in a 'ModuleGraph'. The nodes of the module graph
+-- are one of:
+--
+-- * A regular Haskell source module
+-- * A hi-boot source module
+--
+data ModSummary
+ = ModSummary {
+ ms_mod :: Module,
+ -- ^ Identity of the module
+ ms_hsc_src :: HscSource,
+ -- ^ The module source either plain Haskell or hs-boot
+ ms_location :: ModLocation,
+ -- ^ Location of the various files belonging to the module
+ ms_hs_date :: UTCTime,
+ -- ^ Timestamp of source file
+ ms_obj_date :: Maybe UTCTime,
+ -- ^ Timestamp of object, if we have one
+ ms_iface_date :: Maybe UTCTime,
+ -- ^ Timestamp of hi file, if we *only* are typechecking (it is
+ -- 'Nothing' otherwise.
+ -- See Note [Recompilation checking in -fno-code mode] and #9243
+ ms_hie_date :: Maybe UTCTime,
+ -- ^ Timestamp of hie file, if we have one
+ ms_srcimps :: [(Maybe FastString, Located ModuleName)],
+ -- ^ Source imports of the module
+ ms_textual_imps :: [(Maybe FastString, Located ModuleName)],
+ -- ^ Non-source imports of the module from the module *text*
+ ms_parsed_mod :: Maybe HsParsedModule,
+ -- ^ The parsed, nonrenamed source, if we have it. This is also
+ -- used to support "inline module syntax" in Backpack files.
+ ms_hspp_file :: FilePath,
+ -- ^ Filename of preprocessed source file
+ ms_hspp_opts :: DynFlags,
+ -- ^ Cached flags from @OPTIONS@, @INCLUDE@ and @LANGUAGE@
+ -- pragmas in the modules source code
+ ms_hspp_buf :: Maybe StringBuffer
+ -- ^ The actual preprocessed source, if we have it
+ }
+
+ms_installed_mod :: ModSummary -> InstalledModule
+ms_installed_mod = fst . getModuleInstantiation . ms_mod
+
+ms_mod_name :: ModSummary -> ModuleName
+ms_mod_name = moduleName . ms_mod
+
+ms_imps :: ModSummary -> [(Maybe FastString, Located ModuleName)]
+ms_imps ms =
+ ms_textual_imps ms ++
+ map mk_additional_import (dynFlagDependencies (ms_hspp_opts ms))
+ where
+ mk_additional_import mod_nm = (Nothing, noLoc mod_nm)
+
+home_imps :: [(Maybe FastString, Located ModuleName)] -> [Located ModuleName]
+home_imps imps = [ lmodname | (mb_pkg, lmodname) <- imps,
+ isLocal mb_pkg ]
+ where isLocal Nothing = True
+ isLocal (Just pkg) | pkg == fsLit "this" = True -- "this" is special
+ isLocal _ = False
+
+ms_home_allimps :: ModSummary -> [ModuleName]
+ms_home_allimps ms = map unLoc (ms_home_srcimps ms ++ ms_home_imps ms)
+
+-- | Like 'ms_home_imps', but for SOURCE imports.
+ms_home_srcimps :: ModSummary -> [Located ModuleName]
+ms_home_srcimps = home_imps . ms_srcimps
+
+-- | All of the (possibly) home module imports from a
+-- 'ModSummary'; that is to say, each of these module names
+-- could be a home import if an appropriately named file
+-- existed. (This is in contrast to package qualified
+-- imports, which are guaranteed not to be home imports.)
+ms_home_imps :: ModSummary -> [Located ModuleName]
+ms_home_imps = home_imps . ms_imps
+
+-- The ModLocation contains both the original source filename and the
+-- filename of the cleaned-up source file after all preprocessing has been
+-- done. The point is that the summariser will have to cpp/unlit/whatever
+-- all files anyway, and there's no point in doing this twice -- just
+-- park the result in a temp file, put the name of it in the location,
+-- and let @compile@ read from that file on the way back up.
+
+-- The ModLocation is stable over successive up-sweeps in GHCi, wheres
+-- the ms_hs_date and imports can, of course, change
+
+msHsFilePath, msHiFilePath, msObjFilePath :: ModSummary -> FilePath
+msHsFilePath ms = expectJust "msHsFilePath" (ml_hs_file (ms_location ms))
+msHiFilePath ms = ml_hi_file (ms_location ms)
+msObjFilePath ms = ml_obj_file (ms_location ms)
+
+msDynObjFilePath :: ModSummary -> DynFlags -> FilePath
+msDynObjFilePath ms dflags = dynamicOutputFile dflags (msObjFilePath ms)
+
+-- | Did this 'ModSummary' originate from a hs-boot file?
+isBootSummary :: ModSummary -> IsBootInterface
+isBootSummary ms = if ms_hsc_src ms == HsBootFile then IsBoot else NotBoot
+
+instance Outputable ModSummary where
+ ppr ms
+ = sep [text "ModSummary {",
+ nest 3 (sep [text "ms_hs_date = " <> text (show (ms_hs_date ms)),
+ text "ms_mod =" <+> ppr (ms_mod ms)
+ <> text (hscSourceString (ms_hsc_src ms)) <> comma,
+ text "ms_textual_imps =" <+> ppr (ms_textual_imps ms),
+ text "ms_srcimps =" <+> ppr (ms_srcimps ms)]),
+ char '}'
+ ]
+
+showModMsg :: DynFlags -> Bool -> ModSummary -> SDoc
+showModMsg dflags recomp mod_summary =
+ if gopt Opt_HideSourcePaths dflags
+ then text mod_str
+ else hsep $
+ [ text (mod_str ++ replicate (max 0 (16 - length mod_str)) ' ')
+ , char '('
+ , text (op $ msHsFilePath mod_summary) <> char ','
+ ] ++
+ if gopt Opt_BuildDynamicToo dflags
+ then [ text obj_file <> char ','
+ , text dyn_file
+ , char ')'
+ ]
+ else [ text obj_file, char ')' ]
+ where
+ op = normalise
+ mod = moduleName (ms_mod mod_summary)
+ mod_str = showPpr dflags mod ++ hscSourceString (ms_hsc_src mod_summary)
+ dyn_file = op $ msDynObjFilePath mod_summary dflags
+ obj_file = case backend dflags of
+ Interpreter | recomp -> "interpreted"
+ NoBackend -> "nothing"
+ _ -> (op $ msObjFilePath mod_summary)
+
+findTarget :: ModSummary -> [Target] -> Maybe Target
+findTarget ms ts =
+ case filter (matches ms) ts of
+ [] -> Nothing
+ (t:_) -> Just t
+ where
+ summary `matches` Target (TargetModule m) _ _
+ = ms_mod_name summary == m
+ summary `matches` Target (TargetFile f _) _ _
+ | Just f' <- ml_hs_file (ms_location summary)
+ = f == f'
+ _ `matches` _
+ = False
diff --git a/compiler/GHC/Unit/Module/Status.hs b/compiler/GHC/Unit/Module/Status.hs
new file mode 100644
index 0000000000..d7fb83e582
--- /dev/null
+++ b/compiler/GHC/Unit/Module/Status.hs
@@ -0,0 +1,46 @@
+module GHC.Unit.Module.Status
+ ( HscStatus (..)
+ )
+where
+
+import GHC.Prelude
+
+import GHC.Driver.Session
+
+import GHC.Unit
+import GHC.Unit.Module.ModGuts
+import GHC.Unit.Module.ModIface
+import GHC.Unit.Module.ModDetails
+
+import GHC.Utils.Fingerprint
+
+-- | Status of a module compilation to machine code
+data HscStatus
+ -- | Nothing to do.
+ = HscNotGeneratingCode ModIface ModDetails
+ -- | Nothing to do because code already exists.
+ | HscUpToDate ModIface ModDetails
+ -- | Update boot file result.
+ | HscUpdateBoot ModIface ModDetails
+ -- | Generate signature file (backpack)
+ | HscUpdateSig ModIface ModDetails
+ -- | Recompile this module.
+ | HscRecomp
+ { hscs_guts :: CgGuts
+ -- ^ Information for the code generator.
+ , hscs_mod_location :: !ModLocation
+ -- ^ Module info
+ , hscs_mod_details :: !ModDetails
+ , hscs_partial_iface :: !PartialModIface
+ -- ^ Partial interface
+ , hscs_old_iface_hash :: !(Maybe Fingerprint)
+ -- ^ Old interface hash for this compilation, if an old interface file
+ -- exists. Pass to `hscMaybeWriteIface` when writing the interface to
+ -- avoid updating the existing interface when the interface isn't
+ -- changed.
+ , hscs_iface_dflags :: !DynFlags
+ -- ^ Generate final iface using this DynFlags.
+ -- FIXME (osa): I don't understand why this is necessary, but I spent
+ -- almost two days trying to figure this out and I couldn't .. perhaps
+ -- someone who understands this code better will remove this later.
+ }
diff --git a/compiler/GHC/Unit/Module/Warnings.hs b/compiler/GHC/Unit/Module/Warnings.hs
new file mode 100644
index 0000000000..d8847be72c
--- /dev/null
+++ b/compiler/GHC/Unit/Module/Warnings.hs
@@ -0,0 +1,146 @@
+{-# LANGUAGE DeriveDataTypeable #-}
+
+-- | Warnings for a module
+module GHC.Unit.Module.Warnings
+ ( Warnings (..)
+ , WarningTxt (..)
+ , pprWarningTxtForMsg
+ , mkIfaceWarnCache
+ , emptyIfaceWarnCache
+ , plusWarns
+ )
+where
+
+import GHC.Prelude
+
+import GHC.Types.SourceText
+import GHC.Types.Name.Occurrence
+import GHC.Types.SrcLoc
+
+import GHC.Utils.Outputable
+import GHC.Utils.Binary
+
+import Data.Data
+
+-- | Warning Text
+--
+-- reason/explanation from a WARNING or DEPRECATED pragma
+data WarningTxt
+ = WarningTxt
+ (Located SourceText)
+ [Located StringLiteral]
+ | DeprecatedTxt
+ (Located SourceText)
+ [Located StringLiteral]
+ deriving (Eq, Data)
+
+instance Outputable WarningTxt where
+ ppr (WarningTxt lsrc ws)
+ = case unLoc lsrc of
+ NoSourceText -> pp_ws ws
+ SourceText src -> text src <+> pp_ws ws <+> text "#-}"
+
+ ppr (DeprecatedTxt lsrc ds)
+ = case unLoc lsrc of
+ NoSourceText -> pp_ws ds
+ SourceText src -> text src <+> pp_ws ds <+> text "#-}"
+
+instance Binary WarningTxt where
+ put_ bh (WarningTxt s w) = do
+ putByte bh 0
+ put_ bh s
+ put_ bh w
+ put_ bh (DeprecatedTxt s d) = do
+ putByte bh 1
+ put_ bh s
+ put_ bh d
+
+ get bh = do
+ h <- getByte bh
+ case h of
+ 0 -> do s <- get bh
+ w <- get bh
+ return (WarningTxt s w)
+ _ -> do s <- get bh
+ d <- get bh
+ return (DeprecatedTxt s d)
+
+
+pp_ws :: [Located StringLiteral] -> SDoc
+pp_ws [l] = ppr $ unLoc l
+pp_ws ws
+ = text "["
+ <+> vcat (punctuate comma (map (ppr . unLoc) ws))
+ <+> text "]"
+
+
+pprWarningTxtForMsg :: WarningTxt -> SDoc
+pprWarningTxtForMsg (WarningTxt _ ws)
+ = doubleQuotes (vcat (map (ftext . sl_fs . unLoc) ws))
+pprWarningTxtForMsg (DeprecatedTxt _ ds)
+ = text "Deprecated:" <+>
+ doubleQuotes (vcat (map (ftext . sl_fs . unLoc) ds))
+
+
+-- | Warning information for a module
+data Warnings
+ = NoWarnings -- ^ Nothing deprecated
+ | WarnAll WarningTxt -- ^ Whole module deprecated
+ | WarnSome [(OccName,WarningTxt)] -- ^ Some specific things deprecated
+
+ -- Only an OccName is needed because
+ -- (1) a deprecation always applies to a binding
+ -- defined in the module in which the deprecation appears.
+ -- (2) deprecations are only reported outside the defining module.
+ -- this is important because, otherwise, if we saw something like
+ --
+ -- {-# DEPRECATED f "" #-}
+ -- f = ...
+ -- h = f
+ -- g = let f = undefined in f
+ --
+ -- we'd need more information than an OccName to know to say something
+ -- about the use of f in h but not the use of the locally bound f in g
+ --
+ -- however, because we only report about deprecations from the outside,
+ -- and a module can only export one value called f,
+ -- an OccName suffices.
+ --
+ -- this is in contrast with fixity declarations, where we need to map
+ -- a Name to its fixity declaration.
+ deriving( Eq )
+
+instance Binary Warnings where
+ put_ bh NoWarnings = putByte bh 0
+ put_ bh (WarnAll t) = do
+ putByte bh 1
+ put_ bh t
+ put_ bh (WarnSome ts) = do
+ putByte bh 2
+ put_ bh ts
+
+ get bh = do
+ h <- getByte bh
+ case h of
+ 0 -> return NoWarnings
+ 1 -> do aa <- get bh
+ return (WarnAll aa)
+ _ -> do aa <- get bh
+ return (WarnSome aa)
+
+-- | Constructs the cache for the 'mi_warn_fn' field of a 'ModIface'
+mkIfaceWarnCache :: Warnings -> OccName -> Maybe WarningTxt
+mkIfaceWarnCache NoWarnings = \_ -> Nothing
+mkIfaceWarnCache (WarnAll t) = \_ -> Just t
+mkIfaceWarnCache (WarnSome pairs) = lookupOccEnv (mkOccEnv pairs)
+
+emptyIfaceWarnCache :: OccName -> Maybe WarningTxt
+emptyIfaceWarnCache _ = Nothing
+
+plusWarns :: Warnings -> Warnings -> Warnings
+plusWarns d NoWarnings = d
+plusWarns NoWarnings d = d
+plusWarns _ (WarnAll t) = WarnAll t
+plusWarns (WarnAll t) _ = WarnAll t
+plusWarns (WarnSome v1) (WarnSome v2) = WarnSome (v1 ++ v2)
+