never executed always true always false
    1 -- | Dependencies and Usage of a module
    2 module GHC.Unit.Module.Deps
    3    ( Dependencies
    4    , mkDependencies
    5    , noDependencies
    6    , dep_direct_mods
    7    , dep_direct_pkgs
    8    , dep_sig_mods
    9    , dep_trusted_pkgs
   10    , dep_orphs
   11    , dep_plugin_pkgs
   12    , dep_finsts
   13    , dep_boot_mods
   14    , dep_orphs_update
   15    , dep_finsts_update
   16    , pprDeps
   17    , Usage (..)
   18    , ImportAvails (..)
   19    )
   20 where
   21 
   22 import GHC.Prelude
   23 
   24 import GHC.Types.SafeHaskell
   25 import GHC.Types.Name
   26 import GHC.Types.Unique.FM
   27 
   28 import GHC.Unit.Module.Name
   29 import GHC.Unit.Module.Imported
   30 import GHC.Unit.Module
   31 import GHC.Unit.Home
   32 import GHC.Unit.State
   33 
   34 import GHC.Utils.Fingerprint
   35 import GHC.Utils.Binary
   36 import GHC.Utils.Outputable
   37 
   38 import Data.List (sortBy, sort, partition)
   39 import Data.Set (Set)
   40 import qualified Data.Set as Set
   41 
   42 -- | Dependency information about ALL modules and packages below this one
   43 -- in the import hierarchy. This is the serialisable version of `ImportAvails`.
   44 --
   45 -- Invariant: the dependencies of a module @M@ never includes @M@.
   46 --
   47 -- Invariant: none of the lists contain duplicates.
   48 --
   49 -- Invariant: lists are ordered canonically (e.g. using stableModuleCmp)
   50 --
   51 -- See Note [Transitive Information in Dependencies]
   52 data Dependencies = Deps
   53    { dep_direct_mods :: Set ModuleNameWithIsBoot
   54       -- ^ All home-package modules which are directly imported by this one.
   55 
   56    , dep_direct_pkgs :: Set UnitId
   57       -- ^ All packages directly imported by this module
   58       -- I.e. packages to which this module's direct imports belong.
   59 
   60    , dep_plugin_pkgs :: Set UnitId
   61       -- ^ All units needed for plugins
   62 
   63     ------------------------------------
   64     -- Transitive information below here
   65 
   66    , dep_sig_mods :: ![ModuleName]
   67     -- ^ Transitive closure of hsig files in the home package
   68 
   69 
   70    , dep_trusted_pkgs :: Set UnitId
   71       -- Packages which we are required to trust
   72       -- when the module is imported as a safe import
   73       -- (Safe Haskell). See Note [Tracking Trust Transitively] in GHC.Rename.Names
   74 
   75    , dep_boot_mods :: Set ModuleNameWithIsBoot
   76       -- ^ All modules which have boot files below this one, and whether we
   77       -- should use the boot file or not.
   78       -- This information is only used to populate the eps_is_boot field.
   79       -- See Note [Structure of dep_boot_mods]
   80 
   81    , dep_orphs  :: [Module]
   82       -- ^ Transitive closure of orphan modules (whether
   83       -- home or external pkg).
   84       --
   85       -- (Possible optimization: don't include family
   86       -- instance orphans as they are anyway included in
   87       -- 'dep_finsts'.  But then be careful about code
   88       -- which relies on dep_orphs having the complete list!)
   89       -- This does NOT include us, unlike 'imp_orphs'.
   90 
   91    , dep_finsts :: [Module]
   92       -- ^ Transitive closure of depended upon modules which
   93       -- contain family instances (whether home or external).
   94       -- This is used by 'checkFamInstConsistency'.  This
   95       -- does NOT include us, unlike 'imp_finsts'. See Note
   96       -- [The type family instance consistency story].
   97 
   98    }
   99    deriving( Eq )
  100         -- Equality used only for old/new comparison in GHC.Iface.Recomp.addFingerprints
  101         -- See 'GHC.Tc.Utils.ImportAvails' for details on dependencies.
  102 
  103 
  104 -- | Extract information from the rename and typecheck phases to produce
  105 -- a dependencies information for the module being compiled.
  106 --
  107 -- The fourth argument is a list of plugin modules.
  108 mkDependencies :: HomeUnit -> Module -> ImportAvails -> [Module] -> Dependencies
  109 mkDependencies home_unit mod imports plugin_mods =
  110   let (home_plugins, external_plugins) = partition (isHomeUnit home_unit . moduleUnit) plugin_mods
  111       plugin_units = Set.fromList (map (toUnitId . moduleUnit) external_plugins)
  112       all_direct_mods = foldr (\mn m -> addToUFM m mn (GWIB mn NotBoot))
  113                               (imp_direct_dep_mods imports)
  114                               (map moduleName home_plugins)
  115 
  116       modDepsElts = Set.fromList . nonDetEltsUFM
  117         -- It's OK to use nonDetEltsUFM here because sorting by module names
  118         -- restores determinism
  119 
  120       direct_mods = modDepsElts (delFromUFM all_direct_mods (moduleName mod))
  121             -- M.hi-boot can be in the imp_dep_mods, but we must remove
  122             -- it before recording the modules on which this one depends!
  123             -- (We want to retain M.hi-boot in imp_dep_mods so that
  124             --  loadHiBootInterface can see if M's direct imports depend
  125             --  on M.hi-boot, and hence that we should do the hi-boot consistency
  126             --  check.)
  127 
  128       dep_orphs = filter (/= mod) (imp_orphs imports)
  129             -- We must also remove self-references from imp_orphs. See
  130             -- Note [Module self-dependency]
  131 
  132       direct_pkgs = imp_dep_direct_pkgs imports
  133 
  134       -- Set the packages required to be Safe according to Safe Haskell.
  135       -- See Note [Tracking Trust Transitively] in GHC.Rename.Names
  136       trust_pkgs  = imp_trust_pkgs imports
  137 
  138       -- If there's a non-boot import, then it shadows the boot import
  139       -- coming from the dependencies
  140       source_mods = modDepsElts (imp_boot_mods imports)
  141 
  142       sig_mods = filter (/= (moduleName mod)) $ imp_sig_mods imports
  143 
  144   in Deps { dep_direct_mods  = direct_mods
  145           , dep_direct_pkgs  = direct_pkgs
  146           , dep_plugin_pkgs  = plugin_units
  147           , dep_sig_mods     = sort sig_mods
  148           , dep_trusted_pkgs = trust_pkgs
  149           , dep_boot_mods    = source_mods
  150           , dep_orphs        = sortBy stableModuleCmp dep_orphs
  151           , dep_finsts       = sortBy stableModuleCmp (imp_finsts imports)
  152             -- sort to get into canonical order
  153             -- NB. remember to use lexicographic ordering
  154           }
  155 
  156 -- | Update module dependencies containing orphans (used by Backpack)
  157 dep_orphs_update :: Monad m => Dependencies -> ([Module] -> m [Module]) -> m Dependencies
  158 dep_orphs_update deps f = do
  159   r <- f (dep_orphs deps)
  160   pure (deps { dep_orphs = sortBy stableModuleCmp r })
  161 
  162 -- | Update module dependencies containing family instances (used by Backpack)
  163 dep_finsts_update :: Monad m => Dependencies -> ([Module] -> m [Module]) -> m Dependencies
  164 dep_finsts_update deps f = do
  165   r <- f (dep_finsts deps)
  166   pure (deps { dep_finsts = sortBy stableModuleCmp r })
  167 
  168 
  169 instance Binary Dependencies where
  170     put_ bh deps = do put_ bh (dep_direct_mods deps)
  171                       put_ bh (dep_direct_pkgs deps)
  172                       put_ bh (dep_plugin_pkgs deps)
  173                       put_ bh (dep_trusted_pkgs deps)
  174                       put_ bh (dep_sig_mods deps)
  175                       put_ bh (dep_boot_mods deps)
  176                       put_ bh (dep_orphs deps)
  177                       put_ bh (dep_finsts deps)
  178 
  179     get bh = do dms <- get bh
  180                 dps <- get bh
  181                 plugin_pkgs <- get bh
  182                 tps <- get bh
  183                 hsigms <- get bh
  184                 sms <- get bh
  185                 os <- get bh
  186                 fis <- get bh
  187                 return (Deps { dep_direct_mods = dms
  188                              , dep_direct_pkgs = dps
  189                              , dep_plugin_pkgs = plugin_pkgs
  190                              , dep_sig_mods = hsigms
  191                              , dep_boot_mods = sms
  192                              , dep_trusted_pkgs = tps
  193                              , dep_orphs = os,
  194                                dep_finsts = fis })
  195 
  196 noDependencies :: Dependencies
  197 noDependencies = Deps
  198   { dep_direct_mods  = Set.empty
  199   , dep_direct_pkgs  = Set.empty
  200   , dep_plugin_pkgs  = Set.empty
  201   , dep_sig_mods     = []
  202   , dep_boot_mods    = Set.empty
  203   , dep_trusted_pkgs = Set.empty
  204   , dep_orphs        = []
  205   , dep_finsts       = []
  206   }
  207 
  208 -- | Pretty-print unit dependencies
  209 pprDeps :: UnitState -> Dependencies -> SDoc
  210 pprDeps unit_state (Deps { dep_direct_mods = dmods
  211                          , dep_boot_mods = bmods
  212                          , dep_plugin_pkgs = plgns
  213                          , dep_orphs = orphs
  214                          , dep_direct_pkgs = pkgs
  215                          , dep_trusted_pkgs = tps
  216                          , dep_finsts = finsts
  217                          })
  218   = pprWithUnitState unit_state $
  219     vcat [text "direct module dependencies:"  <+> ppr_set ppr_mod dmods,
  220           text "boot module dependencies:"    <+> ppr_set ppr bmods,
  221           text "direct package dependencies:" <+> ppr_set ppr pkgs,
  222           text "plugin package dependencies:" <+> ppr_set ppr plgns,
  223           if null tps
  224             then empty
  225             else text "trusted package dependencies:" <+> ppr_set ppr tps,
  226           text "orphans:" <+> fsep (map ppr orphs),
  227           text "family instance modules:" <+> fsep (map ppr finsts)
  228         ]
  229   where
  230     ppr_mod (GWIB mod IsBoot)  = ppr mod <+> text "[boot]"
  231     ppr_mod (GWIB mod NotBoot) = ppr mod
  232 
  233     ppr_set :: Outputable a => (a -> SDoc) -> Set a -> SDoc
  234     ppr_set w = fsep . fmap w . Set.toAscList
  235 
  236 -- | Records modules for which changes may force recompilation of this module
  237 -- See wiki: https://gitlab.haskell.org/ghc/ghc/wikis/commentary/compiler/recompilation-avoidance
  238 --
  239 -- This differs from Dependencies.  A module X may be in the dep_mods of this
  240 -- module (via an import chain) but if we don't use anything from X it won't
  241 -- appear in our Usage
  242 data Usage
  243   -- | Module from another package
  244   = UsagePackageModule {
  245         usg_mod      :: Module,
  246            -- ^ External package module depended on
  247         usg_mod_hash :: Fingerprint,
  248             -- ^ Cached module ABI fingerprint (corresponds to mi_mod_hash)
  249         usg_safe :: IsSafeImport
  250             -- ^ Was this module imported as a safe import
  251     }
  252   -- | Module from the current package
  253   | UsageHomeModule {
  254         usg_mod_name :: ModuleName,
  255             -- ^ Name of the module
  256         usg_mod_hash :: Fingerprint,
  257             -- ^ Cached module ABI fingerprint (corresponds to mi_mod_hash).
  258             -- This may be out dated after recompilation was avoided, but is
  259             -- still used as a fast initial check for change during
  260             -- recompilation avoidance.
  261         usg_entities :: [(OccName,Fingerprint)],
  262             -- ^ Entities we depend on, sorted by occurrence name and fingerprinted.
  263             -- NB: usages are for parent names only, e.g. type constructors
  264             -- but not the associated data constructors.
  265         usg_exports  :: Maybe Fingerprint,
  266             -- ^ Fingerprint for the export list of this module,
  267             -- if we directly imported it (and hence we depend on its export list)
  268         usg_safe :: IsSafeImport
  269             -- ^ Was this module imported as a safe import
  270     }                                           -- ^ Module from the current package
  271   -- | A file upon which the module depends, e.g. a CPP #include, or using TH's
  272   -- 'addDependentFile'
  273   | UsageFile {
  274         usg_file_path  :: FilePath,
  275         -- ^ External file dependency. From a CPP #include or TH
  276         -- addDependentFile. Should be absolute.
  277         usg_file_hash  :: Fingerprint,
  278         -- ^ 'Fingerprint' of the file contents.
  279 
  280         usg_file_label :: Maybe String
  281         -- ^ An optional string which is used in recompilation messages if
  282         -- file in question has changed.
  283 
  284         -- Note: We don't consider things like modification timestamps
  285         -- here, because there's no reason to recompile if the actual
  286         -- contents don't change.  This previously lead to odd
  287         -- recompilation behaviors; see #8114
  288   }
  289   | UsageHomeModuleInterface {
  290         usg_mod_name :: ModuleName
  291         -- ^ Name of the module
  292         , usg_iface_hash :: Fingerprint
  293         -- ^ The *interface* hash of the module, not the ABI hash.
  294         -- This changes when anything about the interface (and hence the
  295         -- module) has changed.
  296 
  297         -- UsageHomeModuleInterface is *only* used for recompilation
  298         -- checking when using TemplateHaskell in the interpreter (where
  299         -- some modules are loaded as BCOs).
  300 
  301   }
  302   -- | A requirement which was merged into this one.
  303   | UsageMergedRequirement {
  304         usg_mod :: Module,
  305         usg_mod_hash :: Fingerprint
  306   }
  307     deriving( Eq )
  308         -- The export list field is (Just v) if we depend on the export list:
  309         --      i.e. we imported the module directly, whether or not we
  310         --           enumerated the things we imported, or just imported
  311         --           everything
  312         -- We need to recompile if M's exports change, because
  313         -- if the import was    import M,       we might now have a name clash
  314         --                                      in the importing module.
  315         -- if the import was    import M(x)     M might no longer export x
  316         -- The only way we don't depend on the export list is if we have
  317         --                      import M()
  318         -- And of course, for modules that aren't imported directly we don't
  319         -- depend on their export lists
  320 
  321 instance Binary Usage where
  322     put_ bh usg@UsagePackageModule{} = do
  323         putByte bh 0
  324         put_ bh (usg_mod usg)
  325         put_ bh (usg_mod_hash usg)
  326         put_ bh (usg_safe     usg)
  327 
  328     put_ bh usg@UsageHomeModule{} = do
  329         putByte bh 1
  330         put_ bh (usg_mod_name usg)
  331         put_ bh (usg_mod_hash usg)
  332         put_ bh (usg_exports  usg)
  333         put_ bh (usg_entities usg)
  334         put_ bh (usg_safe     usg)
  335 
  336     put_ bh usg@UsageFile{} = do
  337         putByte bh 2
  338         put_ bh (usg_file_path usg)
  339         put_ bh (usg_file_hash usg)
  340         put_ bh (usg_file_label usg)
  341 
  342     put_ bh usg@UsageMergedRequirement{} = do
  343         putByte bh 3
  344         put_ bh (usg_mod      usg)
  345         put_ bh (usg_mod_hash usg)
  346 
  347     put_ bh usg@UsageHomeModuleInterface{} = do
  348         putByte bh 4
  349         put_ bh (usg_mod_name usg)
  350         put_ bh (usg_iface_hash usg)
  351 
  352     get bh = do
  353         h <- getByte bh
  354         case h of
  355           0 -> do
  356             nm    <- get bh
  357             mod   <- get bh
  358             safe  <- get bh
  359             return UsagePackageModule { usg_mod = nm, usg_mod_hash = mod, usg_safe = safe }
  360           1 -> do
  361             nm    <- get bh
  362             mod   <- get bh
  363             exps  <- get bh
  364             ents  <- get bh
  365             safe  <- get bh
  366             return UsageHomeModule { usg_mod_name = nm, usg_mod_hash = mod,
  367                      usg_exports = exps, usg_entities = ents, usg_safe = safe }
  368           2 -> do
  369             fp   <- get bh
  370             hash <- get bh
  371             label <- get bh
  372             return UsageFile { usg_file_path = fp, usg_file_hash = hash, usg_file_label = label }
  373           3 -> do
  374             mod <- get bh
  375             hash <- get bh
  376             return UsageMergedRequirement { usg_mod = mod, usg_mod_hash = hash }
  377           4 -> do
  378             mod <- get bh
  379             hash <- get bh
  380             return UsageHomeModuleInterface { usg_mod_name = mod, usg_iface_hash = hash }
  381           i -> error ("Binary.get(Usage): " ++ show i)
  382 
  383 
  384 {-
  385 Note [Transitive Information in Dependencies]
  386 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  387 
  388 It is important to be careful what information we put in 'Dependencies' because
  389 ultimately it ends up serialised in an interface file. Interface files must always
  390 be kept up-to-date with the state of the world, so if `Dependencies` needs to be updated
  391 then the module had to be recompiled just to update `Dependencies`.
  392 
  393 Before #16885, the dependencies used to contain the transitive closure of all
  394 home modules. Therefore, if you added an import somewhere low down in the home package
  395 it would recompile nearly every module in your project, just to update this information.
  396 
  397 Now, we are a bit more careful about what we store and
  398 explicitly store transitive information only if it is really needed.
  399 
  400 # Direct Information
  401 
  402 * dep_direct_mods - Directly imported home package modules
  403 * dep_direct_pkgs - Directly imported packages
  404 * dep_plgins      - Directly used plugins
  405 
  406 # Transitive Information
  407 
  408 Some features of the compiler require transitive information about what is currently
  409 being compiled, so that is explicitly stored separately in the form they need.
  410 
  411 * dep_trusted_pkgs - Only used for the -fpackage-trust feature
  412 * dep_boot_mods  - Only used to populate eps_is_boot in -c mode
  413 * dep_orphs        - Modules with orphan instances
  414 * dep_finsts       - Modules with type family instances
  415 
  416 Important note: If you add some transitive information to the interface file then
  417 you need to make sure recompilation is triggered when it could be out of date.
  418 The correct way to do this is to include the transitive information in the export
  419 hash of the module. The export hash is computed in `GHC.Iface.Recomp.addFingerprints`.
  420 -}
  421 
  422 {-
  423 Note [Structure of mod_boot_deps]
  424 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  425 
  426 In `-c` mode we always need to know whether to load the normal or boot version of
  427 an interface file, and this can't be determined from just looking at the direct imports.
  428 
  429 Consider modules with dependencies:
  430 
  431 ```
  432 A -(S)-> B
  433 A -> C -> B -(S)-> B
  434 ```
  435 
  436 Say when compiling module `A` that we need to load the interface for `B`, do we load
  437 `B.hi` or `B.hi-boot`? Well, `A` does directly {-# SOURCE #-} import B, so you might think
  438 that we would load the `B.hi-boot` file, however this is wrong because `C` imports
  439 `B` normally. Therefore in the interface file for `C` we still need to record that
  440 there is a hs-boot file for `B` below it but that we now want `B.hi` rather than
  441 `B.hi-boot`. When `C` is imported, the fact that it needs `B.hi` clobbers the `{- SOURCE -}`
  442 import for `B`.
  443 
  444 Therefore in mod_boot_deps we store the names of any modules which have hs-boot files,
  445 and whether we want to import the .hi or .hi-boot version of the interface file.
  446 
  447 If you get this wrong, then GHC fails to compile, so there is a test but you might
  448 not make it that far if you get this wrong!
  449 
  450 Question: does this happen even across packages?
  451 No: if I need to load the interface for module X from package P I always look for p:X.hi.
  452 
  453 -}
  454 
  455 -- | 'ImportAvails' summarises what was imported from where, irrespective of
  456 -- whether the imported things are actually used or not.  It is used:
  457 --
  458 --  * when processing the export list,
  459 --
  460 --  * when constructing usage info for the interface file,
  461 --
  462 --  * to identify the list of directly imported modules for initialisation
  463 --    purposes and for optimised overlap checking of family instances,
  464 --
  465 --  * when figuring out what things are really unused
  466 --
  467 data ImportAvails
  468    = ImportAvails {
  469         imp_mods :: ImportedMods,
  470           --      = ModuleEnv [ImportedModsVal],
  471           -- ^ Domain is all directly-imported modules
  472           --
  473           -- See the documentation on ImportedModsVal in
  474           -- "GHC.Unit.Module.Imported" for the meaning of the fields.
  475           --
  476           -- We need a full ModuleEnv rather than a ModuleNameEnv here,
  477           -- because we might be importing modules of the same name from
  478           -- different packages. (currently not the case, but might be in the
  479           -- future).
  480 
  481         imp_direct_dep_mods :: ModuleNameEnv ModuleNameWithIsBoot,
  482           -- ^ Home-package modules directly imported by the module being compiled.
  483 
  484         imp_dep_direct_pkgs :: Set UnitId,
  485           -- ^ Packages directly needed by the module being compiled
  486 
  487         imp_trust_own_pkg :: Bool,
  488           -- ^ Do we require that our own package is trusted?
  489           -- This is to handle efficiently the case where a Safe module imports
  490           -- a Trustworthy module that resides in the same package as it.
  491           -- See Note [Trust Own Package] in "GHC.Rename.Names"
  492 
  493         -- Transitive information below here
  494 
  495         imp_trust_pkgs :: Set UnitId,
  496           -- ^ This records the
  497           -- packages the current module needs to trust for Safe Haskell
  498           -- compilation to succeed. A package is required to be trusted if
  499           -- we are dependent on a trustworthy module in that package.
  500           -- See Note [Tracking Trust Transitively] in "GHC.Rename.Names"
  501 
  502         imp_boot_mods :: ModuleNameEnv ModuleNameWithIsBoot,
  503           -- ^ Domain is all modules which have hs-boot files, and whether
  504           -- we should import the boot version of interface file. Only used
  505           -- in one-shot mode to populate eps_is_boot.
  506 
  507         imp_sig_mods :: [ModuleName],
  508           -- ^ Signature modules below this one
  509 
  510         imp_orphs :: [Module],
  511           -- ^ Orphan modules below us in the import tree (and maybe including
  512           -- us for imported modules)
  513 
  514         imp_finsts :: [Module]
  515           -- ^ Family instance modules below us in the import tree (and maybe
  516           -- including us for imported modules)
  517       }