-- | 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
   { Dependencies -> [ModuleNameWithIsBoot]
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

   , Dependencies -> [(UnitId, Bool)]
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

   , Dependencies -> [Module]
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'.

   , Dependencies -> [Module]
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].

   , Dependencies -> [ModuleName]
dep_plgins :: [ModuleName]
      -- ^ All the plugins used while compiling this module.
   }
   deriving( Dependencies -> Dependencies -> Bool
(Dependencies -> Dependencies -> Bool)
-> (Dependencies -> Dependencies -> Bool) -> Eq Dependencies
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Dependencies -> Dependencies -> Bool
$c/= :: Dependencies -> Dependencies -> Bool
== :: Dependencies -> Dependencies -> Bool
$c== :: Dependencies -> Dependencies -> Bool
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_ :: BinHandle -> Dependencies -> IO ()
put_ BinHandle
bh Dependencies
deps = do BinHandle -> [ModuleNameWithIsBoot] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Dependencies -> [ModuleNameWithIsBoot]
dep_mods Dependencies
deps)
                      BinHandle -> [(UnitId, Bool)] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Dependencies -> [(UnitId, Bool)]
dep_pkgs Dependencies
deps)
                      BinHandle -> [Module] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Dependencies -> [Module]
dep_orphs Dependencies
deps)
                      BinHandle -> [Module] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Dependencies -> [Module]
dep_finsts Dependencies
deps)
                      BinHandle -> [ModuleName] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Dependencies -> [ModuleName]
dep_plgins Dependencies
deps)

    get :: BinHandle -> IO Dependencies
get BinHandle
bh = do [ModuleNameWithIsBoot]
ms <- BinHandle -> IO [ModuleNameWithIsBoot]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                [(UnitId, Bool)]
ps <- BinHandle -> IO [(UnitId, Bool)]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                [Module]
os <- BinHandle -> IO [Module]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                [Module]
fis <- BinHandle -> IO [Module]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                [ModuleName]
pl <- BinHandle -> IO [ModuleName]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                Dependencies -> IO Dependencies
forall (m :: * -> *) a. Monad m => a -> m a
return (Deps :: [ModuleNameWithIsBoot]
-> [(UnitId, Bool)]
-> [Module]
-> [Module]
-> [ModuleName]
-> Dependencies
Deps { dep_mods :: [ModuleNameWithIsBoot]
dep_mods = [ModuleNameWithIsBoot]
ms, dep_pkgs :: [(UnitId, Bool)]
dep_pkgs = [(UnitId, Bool)]
ps, dep_orphs :: [Module]
dep_orphs = [Module]
os,
                               dep_finsts :: [Module]
dep_finsts = [Module]
fis, dep_plgins :: [ModuleName]
dep_plgins = [ModuleName]
pl })

noDependencies :: Dependencies
noDependencies :: Dependencies
noDependencies = [ModuleNameWithIsBoot]
-> [(UnitId, Bool)]
-> [Module]
-> [Module]
-> [ModuleName]
-> Dependencies
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 {
        Usage -> Module
usg_mod      :: Module,
           -- ^ External package module depended on
        Usage -> Fingerprint
usg_mod_hash :: Fingerprint,
            -- ^ Cached module fingerprint
        Usage -> Bool
usg_safe :: IsSafeImport
            -- ^ Was this module imported as a safe import
    }
  -- | Module from the current package
  | UsageHomeModule {
        Usage -> ModuleName
usg_mod_name :: ModuleName,
            -- ^ Name of the module
        usg_mod_hash :: Fingerprint,
            -- ^ Cached module fingerprint
        Usage -> [(OccName, 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.
        Usage -> Maybe Fingerprint
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 {
        Usage -> FilePath
usg_file_path  :: FilePath,
        -- ^ External file dependency. From a CPP #include or TH
        -- addDependentFile. Should be absolute.
        Usage -> Fingerprint
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( Usage -> Usage -> Bool
(Usage -> Usage -> Bool) -> (Usage -> Usage -> Bool) -> Eq Usage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Usage -> Usage -> Bool
$c/= :: Usage -> Usage -> Bool
== :: Usage -> Usage -> Bool
$c== :: Usage -> Usage -> Bool
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_ :: BinHandle -> Usage -> IO ()
put_ BinHandle
bh usg :: Usage
usg@UsagePackageModule{} = do
        BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
        BinHandle -> Module -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> Module
usg_mod Usage
usg)
        BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> Fingerprint
usg_mod_hash Usage
usg)
        BinHandle -> Bool -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> Bool
usg_safe     Usage
usg)

    put_ BinHandle
bh usg :: Usage
usg@UsageHomeModule{} = do
        BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
        BinHandle -> ModuleName -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> ModuleName
usg_mod_name Usage
usg)
        BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> Fingerprint
usg_mod_hash Usage
usg)
        BinHandle -> Maybe Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> Maybe Fingerprint
usg_exports  Usage
usg)
        BinHandle -> [(OccName, Fingerprint)] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> [(OccName, Fingerprint)]
usg_entities Usage
usg)
        BinHandle -> Bool -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> Bool
usg_safe     Usage
usg)

    put_ BinHandle
bh usg :: Usage
usg@UsageFile{} = do
        BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2
        BinHandle -> FilePath -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> FilePath
usg_file_path Usage
usg)
        BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> Fingerprint
usg_file_hash Usage
usg)

    put_ BinHandle
bh usg :: Usage
usg@UsageMergedRequirement{} = do
        BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
3
        BinHandle -> Module -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> Module
usg_mod      Usage
usg)
        BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> Fingerprint
usg_mod_hash Usage
usg)

    get :: BinHandle -> IO Usage
get BinHandle
bh = do
        Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
        case Word8
h of
          Word8
0 -> do
            Module
nm    <- BinHandle -> IO Module
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Fingerprint
mod   <- BinHandle -> IO Fingerprint
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Bool
safe  <- BinHandle -> IO Bool
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Usage -> IO Usage
forall (m :: * -> *) a. Monad m => a -> m a
return UsagePackageModule :: Module -> Fingerprint -> Bool -> Usage
UsagePackageModule { usg_mod :: Module
usg_mod = Module
nm, usg_mod_hash :: Fingerprint
usg_mod_hash = Fingerprint
mod, usg_safe :: Bool
usg_safe = Bool
safe }
          Word8
1 -> do
            ModuleName
nm    <- BinHandle -> IO ModuleName
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Fingerprint
mod   <- BinHandle -> IO Fingerprint
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Maybe Fingerprint
exps  <- BinHandle -> IO (Maybe Fingerprint)
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            [(OccName, Fingerprint)]
ents  <- BinHandle -> IO [(OccName, Fingerprint)]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Bool
safe  <- BinHandle -> IO Bool
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Usage -> IO Usage
forall (m :: * -> *) a. Monad m => a -> m a
return UsageHomeModule :: ModuleName
-> Fingerprint
-> [(OccName, Fingerprint)]
-> Maybe Fingerprint
-> Bool
-> Usage
UsageHomeModule { usg_mod_name :: ModuleName
usg_mod_name = ModuleName
nm, usg_mod_hash :: Fingerprint
usg_mod_hash = Fingerprint
mod,
                     usg_exports :: Maybe Fingerprint
usg_exports = Maybe Fingerprint
exps, usg_entities :: [(OccName, Fingerprint)]
usg_entities = [(OccName, Fingerprint)]
ents, usg_safe :: Bool
usg_safe = Bool
safe }
          Word8
2 -> do
            FilePath
fp   <- BinHandle -> IO FilePath
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Fingerprint
hash <- BinHandle -> IO Fingerprint
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Usage -> IO Usage
forall (m :: * -> *) a. Monad m => a -> m a
return UsageFile :: FilePath -> Fingerprint -> Usage
UsageFile { usg_file_path :: FilePath
usg_file_path = FilePath
fp, usg_file_hash :: Fingerprint
usg_file_hash = Fingerprint
hash }
          Word8
3 -> do
            Module
mod <- BinHandle -> IO Module
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Fingerprint
hash <- BinHandle -> IO Fingerprint
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Usage -> IO Usage
forall (m :: * -> *) a. Monad m => a -> m a
return UsageMergedRequirement :: Module -> Fingerprint -> Usage
UsageMergedRequirement { usg_mod :: Module
usg_mod = Module
mod, usg_mod_hash :: Fingerprint
usg_mod_hash = Fingerprint
hash }
          Word8
i -> FilePath -> IO Usage
forall a. HasCallStack => FilePath -> a
error (FilePath
"Binary.get(Usage): " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Word8 -> FilePath
forall a. Show a => a -> FilePath
show Word8
i)