module GHC.Unit.Module.Deps
   ( Dependencies
   , mkDependencies
   , noDependencies
   , dep_direct_mods
   , dep_direct_pkgs
   , dep_sig_mods
   , dep_trusted_pkgs
   , dep_orphs
   , dep_plugin_pkgs
   , dep_finsts
   , dep_boot_mods
   , dep_orphs_update
   , dep_finsts_update
   , pprDeps
   , Usage (..)
   , ImportAvails (..)
   )
where
import GHC.Prelude
import GHC.Types.SafeHaskell
import GHC.Types.Name
import GHC.Unit.Module.Name
import GHC.Unit.Module.Imported
import GHC.Unit.Module
import GHC.Unit.Home
import GHC.Unit.State
import GHC.Utils.Fingerprint
import GHC.Utils.Binary
import GHC.Utils.Outputable
import Data.List (sortBy, sort, partition)
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Bifunctor
data Dependencies = Deps
   { Dependencies -> Set (UnitId, GenWithIsBoot ModuleName)
dep_direct_mods :: Set (UnitId, ModuleNameWithIsBoot)
      
      
   , Dependencies -> Set UnitId
dep_direct_pkgs :: Set UnitId
      
      
      
      
   , Dependencies -> Set UnitId
dep_plugin_pkgs :: Set UnitId
      
    
    
   , Dependencies -> [ModuleName]
dep_sig_mods :: ![ModuleName]
    
   , Dependencies -> Set UnitId
dep_trusted_pkgs :: Set UnitId
      
      
      
   , Dependencies -> Set (UnitId, GenWithIsBoot ModuleName)
dep_boot_mods :: Set (UnitId, ModuleNameWithIsBoot)
      
      
      
      
   , Dependencies -> [Module]
dep_orphs  :: [Module]
      
      
      
      
      
      
      
      
   , Dependencies -> [Module]
dep_finsts :: [Module]
      
      
      
      
      
   }
   deriving( Dependencies -> Dependencies -> Bool
(Dependencies -> Dependencies -> Bool)
-> (Dependencies -> Dependencies -> Bool) -> Eq Dependencies
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Dependencies -> Dependencies -> Bool
== :: Dependencies -> Dependencies -> Bool
$c/= :: Dependencies -> Dependencies -> Bool
/= :: Dependencies -> Dependencies -> Bool
Eq )
        
        
mkDependencies :: HomeUnit -> Module -> ImportAvails -> [Module] -> Dependencies
mkDependencies :: HomeUnit -> Module -> ImportAvails -> [Module] -> Dependencies
mkDependencies HomeUnit
home_unit Module
mod ImportAvails
imports [Module]
plugin_mods =
  let ([Module]
home_plugins, [Module]
external_plugins) = (Module -> Bool) -> [Module] -> ([Module], [Module])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition (HomeUnit -> GenUnit UnitId -> Bool
isHomeUnit HomeUnit
home_unit (GenUnit UnitId -> Bool)
-> (Module -> GenUnit UnitId) -> Module -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Module -> GenUnit UnitId
forall unit. GenModule unit -> unit
moduleUnit) [Module]
plugin_mods
      plugin_units :: Set UnitId
plugin_units = [UnitId] -> Set UnitId
forall a. Ord a => [a] -> Set a
Set.fromList ((Module -> UnitId) -> [Module] -> [UnitId]
forall a b. (a -> b) -> [a] -> [b]
map (GenUnit UnitId -> UnitId
toUnitId (GenUnit UnitId -> UnitId)
-> (Module -> GenUnit UnitId) -> Module -> UnitId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Module -> GenUnit UnitId
forall unit. GenModule unit -> unit
moduleUnit) [Module]
external_plugins)
      all_direct_mods :: InstalledModuleEnv (GenWithIsBoot ModuleName)
all_direct_mods = (InstalledModule
 -> InstalledModuleEnv (GenWithIsBoot ModuleName)
 -> InstalledModuleEnv (GenWithIsBoot ModuleName))
-> InstalledModuleEnv (GenWithIsBoot ModuleName)
-> [InstalledModule]
-> InstalledModuleEnv (GenWithIsBoot ModuleName)
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\InstalledModule
mn InstalledModuleEnv (GenWithIsBoot ModuleName)
m -> InstalledModuleEnv (GenWithIsBoot ModuleName)
-> InstalledModule
-> GenWithIsBoot ModuleName
-> InstalledModuleEnv (GenWithIsBoot ModuleName)
forall a.
InstalledModuleEnv a
-> InstalledModule -> a -> InstalledModuleEnv a
extendInstalledModuleEnv InstalledModuleEnv (GenWithIsBoot ModuleName)
m InstalledModule
mn (ModuleName -> IsBootInterface -> GenWithIsBoot ModuleName
forall mod. mod -> IsBootInterface -> GenWithIsBoot mod
GWIB (InstalledModule -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName InstalledModule
mn) IsBootInterface
NotBoot))
                              (ImportAvails -> InstalledModuleEnv (GenWithIsBoot ModuleName)
imp_direct_dep_mods ImportAvails
imports)
                              ((Module -> InstalledModule) -> [Module] -> [InstalledModule]
forall a b. (a -> b) -> [a] -> [b]
map ((GenUnit UnitId -> UnitId) -> Module -> InstalledModule
forall a b. (a -> b) -> GenModule a -> GenModule b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap GenUnit UnitId -> UnitId
toUnitId) [Module]
home_plugins)
      modDepsElts :: InstalledModuleEnv (GenWithIsBoot ModuleName)
-> Set (InstalledModule, GenWithIsBoot ModuleName)
modDepsElts = [(InstalledModule, GenWithIsBoot ModuleName)]
-> Set (InstalledModule, GenWithIsBoot ModuleName)
forall a. Ord a => [a] -> Set a
Set.fromList ([(InstalledModule, GenWithIsBoot ModuleName)]
 -> Set (InstalledModule, GenWithIsBoot ModuleName))
-> (InstalledModuleEnv (GenWithIsBoot ModuleName)
    -> [(InstalledModule, GenWithIsBoot ModuleName)])
-> InstalledModuleEnv (GenWithIsBoot ModuleName)
-> Set (InstalledModule, GenWithIsBoot ModuleName)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InstalledModuleEnv (GenWithIsBoot ModuleName)
-> [(InstalledModule, GenWithIsBoot ModuleName)]
forall a. InstalledModuleEnv a -> [(InstalledModule, a)]
installedModuleEnvElts
        
        
      direct_mods :: Set (UnitId, GenWithIsBoot ModuleName)
direct_mods = (InstalledModule -> UnitId)
-> (InstalledModule, GenWithIsBoot ModuleName)
-> (UnitId, GenWithIsBoot ModuleName)
forall a b c. (a -> b) -> (a, c) -> (b, c)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first InstalledModule -> UnitId
forall unit. GenModule unit -> unit
moduleUnit ((InstalledModule, GenWithIsBoot ModuleName)
 -> (UnitId, GenWithIsBoot ModuleName))
-> Set (InstalledModule, GenWithIsBoot ModuleName)
-> Set (UnitId, GenWithIsBoot ModuleName)
forall b a. Ord b => (a -> b) -> Set a -> Set b
`Set.map` InstalledModuleEnv (GenWithIsBoot ModuleName)
-> Set (InstalledModule, GenWithIsBoot ModuleName)
modDepsElts (InstalledModuleEnv (GenWithIsBoot ModuleName)
-> InstalledModule -> InstalledModuleEnv (GenWithIsBoot ModuleName)
forall a.
InstalledModuleEnv a -> InstalledModule -> InstalledModuleEnv a
delInstalledModuleEnv InstalledModuleEnv (GenWithIsBoot ModuleName)
all_direct_mods (GenUnit UnitId -> UnitId
toUnitId (GenUnit UnitId -> UnitId) -> Module -> InstalledModule
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Module
mod))
            
            
            
            
            
            
      dep_orphs :: [Module]
dep_orphs = (Module -> Bool) -> [Module] -> [Module]
forall a. (a -> Bool) -> [a] -> [a]
filter (Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
/= Module
mod) (ImportAvails -> [Module]
imp_orphs ImportAvails
imports)
            
            
      direct_pkgs :: Set UnitId
direct_pkgs = ImportAvails -> Set UnitId
imp_dep_direct_pkgs ImportAvails
imports
      
      
      trust_pkgs :: Set UnitId
trust_pkgs  = ImportAvails -> Set UnitId
imp_trust_pkgs ImportAvails
imports
      
      
      source_mods :: Set (UnitId, GenWithIsBoot ModuleName)
source_mods = (InstalledModule -> UnitId)
-> (InstalledModule, GenWithIsBoot ModuleName)
-> (UnitId, GenWithIsBoot ModuleName)
forall a b c. (a -> b) -> (a, c) -> (b, c)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first InstalledModule -> UnitId
forall unit. GenModule unit -> unit
moduleUnit ((InstalledModule, GenWithIsBoot ModuleName)
 -> (UnitId, GenWithIsBoot ModuleName))
-> Set (InstalledModule, GenWithIsBoot ModuleName)
-> Set (UnitId, GenWithIsBoot ModuleName)
forall b a. Ord b => (a -> b) -> Set a -> Set b
`Set.map` InstalledModuleEnv (GenWithIsBoot ModuleName)
-> Set (InstalledModule, GenWithIsBoot ModuleName)
modDepsElts (ImportAvails -> InstalledModuleEnv (GenWithIsBoot ModuleName)
imp_boot_mods ImportAvails
imports)
      sig_mods :: [ModuleName]
sig_mods = (ModuleName -> Bool) -> [ModuleName] -> [ModuleName]
forall a. (a -> Bool) -> [a] -> [a]
filter (ModuleName -> ModuleName -> Bool
forall a. Eq a => a -> a -> Bool
/= (Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
mod)) ([ModuleName] -> [ModuleName]) -> [ModuleName] -> [ModuleName]
forall a b. (a -> b) -> a -> b
$ ImportAvails -> [ModuleName]
imp_sig_mods ImportAvails
imports
  in Deps { dep_direct_mods :: Set (UnitId, GenWithIsBoot ModuleName)
dep_direct_mods  = Set (UnitId, GenWithIsBoot ModuleName)
direct_mods
          , dep_direct_pkgs :: Set UnitId
dep_direct_pkgs  = Set UnitId
direct_pkgs
          , dep_plugin_pkgs :: Set UnitId
dep_plugin_pkgs  = Set UnitId
plugin_units
          , dep_sig_mods :: [ModuleName]
dep_sig_mods     = [ModuleName] -> [ModuleName]
forall a. Ord a => [a] -> [a]
sort [ModuleName]
sig_mods
          , dep_trusted_pkgs :: Set UnitId
dep_trusted_pkgs = Set UnitId
trust_pkgs
          , dep_boot_mods :: Set (UnitId, GenWithIsBoot ModuleName)
dep_boot_mods    = Set (UnitId, GenWithIsBoot ModuleName)
source_mods
          , dep_orphs :: [Module]
dep_orphs        = (Module -> Module -> Ordering) -> [Module] -> [Module]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy Module -> Module -> Ordering
stableModuleCmp [Module]
dep_orphs
          , dep_finsts :: [Module]
dep_finsts       = (Module -> Module -> Ordering) -> [Module] -> [Module]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy Module -> Module -> Ordering
stableModuleCmp (ImportAvails -> [Module]
imp_finsts ImportAvails
imports)
            
            
          }
dep_orphs_update :: Monad m => Dependencies -> ([Module] -> m [Module]) -> m Dependencies
dep_orphs_update :: forall (m :: * -> *).
Monad m =>
Dependencies -> ([Module] -> m [Module]) -> m Dependencies
dep_orphs_update Dependencies
deps [Module] -> m [Module]
f = do
  [Module]
r <- [Module] -> m [Module]
f (Dependencies -> [Module]
dep_orphs Dependencies
deps)
  Dependencies -> m Dependencies
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Dependencies
deps { dep_orphs :: [Module]
dep_orphs = (Module -> Module -> Ordering) -> [Module] -> [Module]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy Module -> Module -> Ordering
stableModuleCmp [Module]
r })
dep_finsts_update :: Monad m => Dependencies -> ([Module] -> m [Module]) -> m Dependencies
dep_finsts_update :: forall (m :: * -> *).
Monad m =>
Dependencies -> ([Module] -> m [Module]) -> m Dependencies
dep_finsts_update Dependencies
deps [Module] -> m [Module]
f = do
  [Module]
r <- [Module] -> m [Module]
f (Dependencies -> [Module]
dep_finsts Dependencies
deps)
  Dependencies -> m Dependencies
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Dependencies
deps { dep_finsts :: [Module]
dep_finsts = (Module -> Module -> Ordering) -> [Module] -> [Module]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy Module -> Module -> Ordering
stableModuleCmp [Module]
r })
instance Binary Dependencies where
    put_ :: BinHandle -> Dependencies -> IO ()
put_ BinHandle
bh Dependencies
deps = do BinHandle -> Set (UnitId, GenWithIsBoot ModuleName) -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Dependencies -> Set (UnitId, GenWithIsBoot ModuleName)
dep_direct_mods Dependencies
deps)
                      BinHandle -> Set UnitId -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Dependencies -> Set UnitId
dep_direct_pkgs Dependencies
deps)
                      BinHandle -> Set UnitId -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Dependencies -> Set UnitId
dep_plugin_pkgs Dependencies
deps)
                      BinHandle -> Set UnitId -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Dependencies -> Set UnitId
dep_trusted_pkgs Dependencies
deps)
                      BinHandle -> [ModuleName] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Dependencies -> [ModuleName]
dep_sig_mods Dependencies
deps)
                      BinHandle -> Set (UnitId, GenWithIsBoot ModuleName) -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Dependencies -> Set (UnitId, GenWithIsBoot ModuleName)
dep_boot_mods 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)
    get :: BinHandle -> IO Dependencies
get BinHandle
bh = do Set (UnitId, GenWithIsBoot ModuleName)
dms <- BinHandle -> IO (Set (UnitId, GenWithIsBoot ModuleName))
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                Set UnitId
dps <- BinHandle -> IO (Set UnitId)
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                Set UnitId
plugin_pkgs <- BinHandle -> IO (Set UnitId)
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                Set UnitId
tps <- BinHandle -> IO (Set UnitId)
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                [ModuleName]
hsigms <- BinHandle -> IO [ModuleName]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                Set (UnitId, GenWithIsBoot ModuleName)
sms <- BinHandle -> IO (Set (UnitId, GenWithIsBoot ModuleName))
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
                Dependencies -> IO Dependencies
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Deps { dep_direct_mods :: Set (UnitId, GenWithIsBoot ModuleName)
dep_direct_mods = Set (UnitId, GenWithIsBoot ModuleName)
dms
                             , dep_direct_pkgs :: Set UnitId
dep_direct_pkgs = Set UnitId
dps
                             , dep_plugin_pkgs :: Set UnitId
dep_plugin_pkgs = Set UnitId
plugin_pkgs
                             , dep_sig_mods :: [ModuleName]
dep_sig_mods = [ModuleName]
hsigms
                             , dep_boot_mods :: Set (UnitId, GenWithIsBoot ModuleName)
dep_boot_mods = Set (UnitId, GenWithIsBoot ModuleName)
sms
                             , dep_trusted_pkgs :: Set UnitId
dep_trusted_pkgs = Set UnitId
tps
                             , dep_orphs :: [Module]
dep_orphs = [Module]
os,
                               dep_finsts :: [Module]
dep_finsts = [Module]
fis })
noDependencies :: Dependencies
noDependencies :: Dependencies
noDependencies = Deps
  { dep_direct_mods :: Set (UnitId, GenWithIsBoot ModuleName)
dep_direct_mods  = Set (UnitId, GenWithIsBoot ModuleName)
forall a. Set a
Set.empty
  , dep_direct_pkgs :: Set UnitId
dep_direct_pkgs  = Set UnitId
forall a. Set a
Set.empty
  , dep_plugin_pkgs :: Set UnitId
dep_plugin_pkgs  = Set UnitId
forall a. Set a
Set.empty
  , dep_sig_mods :: [ModuleName]
dep_sig_mods     = []
  , dep_boot_mods :: Set (UnitId, GenWithIsBoot ModuleName)
dep_boot_mods    = Set (UnitId, GenWithIsBoot ModuleName)
forall a. Set a
Set.empty
  , dep_trusted_pkgs :: Set UnitId
dep_trusted_pkgs = Set UnitId
forall a. Set a
Set.empty
  , dep_orphs :: [Module]
dep_orphs        = []
  , dep_finsts :: [Module]
dep_finsts       = []
  }
pprDeps :: UnitState -> Dependencies -> SDoc
pprDeps :: UnitState -> Dependencies -> SDoc
pprDeps UnitState
unit_state (Deps { dep_direct_mods :: Dependencies -> Set (UnitId, GenWithIsBoot ModuleName)
dep_direct_mods = Set (UnitId, GenWithIsBoot ModuleName)
dmods
                         , dep_boot_mods :: Dependencies -> Set (UnitId, GenWithIsBoot ModuleName)
dep_boot_mods = Set (UnitId, GenWithIsBoot ModuleName)
bmods
                         , dep_plugin_pkgs :: Dependencies -> Set UnitId
dep_plugin_pkgs = Set UnitId
plgns
                         , dep_orphs :: Dependencies -> [Module]
dep_orphs = [Module]
orphs
                         , dep_direct_pkgs :: Dependencies -> Set UnitId
dep_direct_pkgs = Set UnitId
pkgs
                         , dep_trusted_pkgs :: Dependencies -> Set UnitId
dep_trusted_pkgs = Set UnitId
tps
                         , dep_finsts :: Dependencies -> [Module]
dep_finsts = [Module]
finsts
                         })
  = UnitState -> SDoc -> SDoc
pprWithUnitState UnitState
unit_state (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$
    [SDoc] -> SDoc
vcat [String -> SDoc
text String
"direct module dependencies:"  SDoc -> SDoc -> SDoc
<+> ((UnitId, GenWithIsBoot ModuleName) -> SDoc)
-> Set (UnitId, GenWithIsBoot ModuleName) -> SDoc
forall a. Outputable a => (a -> SDoc) -> Set a -> SDoc
ppr_set (UnitId, GenWithIsBoot ModuleName) -> SDoc
forall {a} {a}.
(Outputable a, Outputable a) =>
(a, GenWithIsBoot a) -> SDoc
ppr_mod Set (UnitId, GenWithIsBoot ModuleName)
dmods,
          String -> SDoc
text String
"boot module dependencies:"    SDoc -> SDoc -> SDoc
<+> ((UnitId, GenWithIsBoot ModuleName) -> SDoc)
-> Set (UnitId, GenWithIsBoot ModuleName) -> SDoc
forall a. Outputable a => (a -> SDoc) -> Set a -> SDoc
ppr_set (UnitId, GenWithIsBoot ModuleName) -> SDoc
forall a. Outputable a => a -> SDoc
ppr Set (UnitId, GenWithIsBoot ModuleName)
bmods,
          String -> SDoc
text String
"direct package dependencies:" SDoc -> SDoc -> SDoc
<+> (UnitId -> SDoc) -> Set UnitId -> SDoc
forall a. Outputable a => (a -> SDoc) -> Set a -> SDoc
ppr_set UnitId -> SDoc
forall a. Outputable a => a -> SDoc
ppr Set UnitId
pkgs,
          String -> SDoc
text String
"plugin package dependencies:" SDoc -> SDoc -> SDoc
<+> (UnitId -> SDoc) -> Set UnitId -> SDoc
forall a. Outputable a => (a -> SDoc) -> Set a -> SDoc
ppr_set UnitId -> SDoc
forall a. Outputable a => a -> SDoc
ppr Set UnitId
plgns,
          if Set UnitId -> Bool
forall a. Set a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Set UnitId
tps
            then SDoc
empty
            else String -> SDoc
text String
"trusted package dependencies:" SDoc -> SDoc -> SDoc
<+> (UnitId -> SDoc) -> Set UnitId -> SDoc
forall a. Outputable a => (a -> SDoc) -> Set a -> SDoc
ppr_set UnitId -> SDoc
forall a. Outputable a => a -> SDoc
ppr Set UnitId
tps,
          String -> SDoc
text String
"orphans:" SDoc -> SDoc -> SDoc
<+> [SDoc] -> SDoc
fsep ((Module -> SDoc) -> [Module] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Module]
orphs),
          String -> SDoc
text String
"family instance modules:" SDoc -> SDoc -> SDoc
<+> [SDoc] -> SDoc
fsep ((Module -> SDoc) -> [Module] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Module]
finsts)
        ]
  where
    ppr_mod :: (a, GenWithIsBoot a) -> SDoc
ppr_mod (a
uid, (GWIB a
mod IsBootInterface
IsBoot))  = a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
uid SDoc -> SDoc -> SDoc
<> SDoc
colon SDoc -> SDoc -> SDoc
<> a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
mod SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"[boot]"
    ppr_mod (a
uid, (GWIB a
mod IsBootInterface
NotBoot)) = a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
uid SDoc -> SDoc -> SDoc
<> SDoc
colon SDoc -> SDoc -> SDoc
<> a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
mod
    ppr_set :: Outputable a => (a -> SDoc) -> Set a -> SDoc
    ppr_set :: forall a. Outputable a => (a -> SDoc) -> Set a -> SDoc
ppr_set a -> SDoc
w = [SDoc] -> SDoc
fsep ([SDoc] -> SDoc) -> (Set a -> [SDoc]) -> Set a -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> SDoc) -> [a] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> SDoc
w ([a] -> [SDoc]) -> (Set a -> [a]) -> Set a -> [SDoc]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set a -> [a]
forall a. Set a -> [a]
Set.toAscList
data Usage
  
  = UsagePackageModule {
        Usage -> Module
usg_mod      :: Module,
           
        Usage -> Fingerprint
usg_mod_hash :: Fingerprint,
            
        Usage -> Bool
usg_safe :: IsSafeImport
            
    }
  
  | UsageHomeModule {
        Usage -> ModuleName
usg_mod_name :: ModuleName,
            
        usg_mod_hash :: Fingerprint,
            
            
            
            
        Usage -> [(OccName, Fingerprint)]
usg_entities :: [(OccName,Fingerprint)],
            
            
            
        Usage -> Maybe Fingerprint
usg_exports  :: Maybe Fingerprint,
            
            
        usg_safe :: IsSafeImport
            
    }
  
  
  | UsageFile {
        Usage -> String
usg_file_path  :: FilePath,
        
        
        Usage -> Fingerprint
usg_file_hash  :: Fingerprint,
        
        Usage -> Maybe String
usg_file_label :: Maybe String
        
        
        
        
        
        
  }
  | UsageHomeModuleInterface {
        usg_mod_name :: ModuleName
        
        , Usage -> Fingerprint
usg_iface_hash :: Fingerprint
        
        
        
        
        
        
  }
  
  | 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
$c== :: Usage -> Usage -> Bool
== :: Usage -> Usage -> Bool
$c/= :: Usage -> Usage -> Bool
/= :: Usage -> Usage -> Bool
Eq )
        
        
        
        
        
        
        
        
        
        
        
        
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 -> String -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> String
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)
        BinHandle -> Maybe String -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> Maybe String
usg_file_label 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)
    put_ BinHandle
bh usg :: Usage
usg@UsageHomeModuleInterface{} = do
        BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
4
        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_iface_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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return 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
            String
fp   <- BinHandle -> IO String
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
            Maybe String
label <- BinHandle -> IO (Maybe String)
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Usage -> IO Usage
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return UsageFile { usg_file_path :: String
usg_file_path = String
fp, usg_file_hash :: Fingerprint
usg_file_hash = Fingerprint
hash, usg_file_label :: Maybe String
usg_file_label = Maybe String
label }
          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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return UsageMergedRequirement { usg_mod :: Module
usg_mod = Module
mod, usg_mod_hash :: Fingerprint
usg_mod_hash = Fingerprint
hash }
          Word8
4 -> do
            ModuleName
mod <- BinHandle -> IO ModuleName
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return UsageHomeModuleInterface { usg_mod_name :: ModuleName
usg_mod_name = ModuleName
mod, usg_iface_hash :: Fingerprint
usg_iface_hash = Fingerprint
hash }
          Word8
i -> String -> IO Usage
forall a. HasCallStack => String -> a
error (String
"Binary.get(Usage): " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Word8 -> String
forall a. Show a => a -> String
show Word8
i)
data ImportAvails
   = ImportAvails {
        ImportAvails -> ImportedMods
imp_mods :: ImportedMods,
          
          
          
          
          
          
          
          
          
          
        ImportAvails -> InstalledModuleEnv (GenWithIsBoot ModuleName)
imp_direct_dep_mods :: InstalledModuleEnv ModuleNameWithIsBoot,
          
        ImportAvails -> Set UnitId
imp_dep_direct_pkgs :: Set UnitId,
          
        ImportAvails -> Bool
imp_trust_own_pkg :: Bool,
          
          
          
          
        
        ImportAvails -> Set UnitId
imp_trust_pkgs :: Set UnitId,
          
          
          
          
          
        ImportAvails -> InstalledModuleEnv (GenWithIsBoot ModuleName)
imp_boot_mods :: InstalledModuleEnv ModuleNameWithIsBoot,
          
          
          
        ImportAvails -> [ModuleName]
imp_sig_mods :: [ModuleName],
          
        ImportAvails -> [Module]
imp_orphs :: [Module],
          
          
        ImportAvails -> [Module]
imp_finsts :: [Module]
          
          
      }