summaryrefslogtreecommitdiff
path: root/compiler/GHC/Unit/Module/ModSummary.hs
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/GHC/Unit/Module/ModSummary.hs')
-rw-r--r--compiler/GHC/Unit/Module/ModSummary.hs57
1 files changed, 25 insertions, 32 deletions
diff --git a/compiler/GHC/Unit/Module/ModSummary.hs b/compiler/GHC/Unit/Module/ModSummary.hs
index a0b42fc2a4..e9106d44eb 100644
--- a/compiler/GHC/Unit/Module/ModSummary.hs
+++ b/compiler/GHC/Unit/Module/ModSummary.hs
@@ -1,7 +1,11 @@
+{-# LANGUAGE LambdaCase #-}
+
-- | A ModSummary is a node in the compilation manager's dependency graph
-- (ModuleGraph)
module GHC.Unit.Module.ModSummary
- ( ModSummary (..)
+ ( ExtendedModSummary (..)
+ , extendModSummaryNoDeps
+ , ModSummary (..)
, ms_installed_mod
, ms_mod_name
, ms_imps
@@ -13,7 +17,6 @@ module GHC.Unit.Module.ModSummary
, msObjFilePath
, msDynObjFilePath
, isBootSummary
- , showModMsg
, findTarget
)
where
@@ -22,9 +25,7 @@ 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
@@ -40,9 +41,24 @@ 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
+-- | Enrichment of 'ModSummary' with backpack dependencies
+data ExtendedModSummary = ExtendedModSummary
+ { emsModSummary :: {-# UNPACK #-} !ModSummary
+ , emsInstantiatedUnits :: [InstantiatedUnit]
+ -- ^ Extra backpack deps
+ -- NB: This is sometimes left empty in situations where the instantiated units
+ -- would not be used. See call sites of 'extendModSummaryNoDeps'.
+ }
+
+instance Outputable ExtendedModSummary where
+ ppr = \case
+ ExtendedModSummary ms bds -> ppr ms <+> ppr bds
+
+extendModSummaryNoDeps :: ModSummary -> ExtendedModSummary
+extendModSummaryNoDeps ms = ExtendedModSummary ms []
+
+-- | Data for a module node in a 'ModuleGraph'. Module nodes of the module graph
-- are one of:
--
-- * A regular Haskell source module
@@ -53,7 +69,7 @@ data ModSummary
ms_mod :: Module,
-- ^ Identity of the module
ms_hsc_src :: HscSource,
- -- ^ The module source either plain Haskell or hs-boot
+ -- ^ The module source either plain Haskell, hs-boot, or hsig
ms_location :: ModLocation,
-- ^ Location of the various files belonging to the module
ms_hs_date :: UTCTime,
@@ -150,31 +166,6 @@ instance Outputable ModSummary where
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
@@ -188,3 +179,5 @@ findTarget ms ts =
= f == f'
_ `matches` _
= False
+
+