{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ExplicitNamespaces #-}
{-# LANGUAGE DerivingVia #-}
module GHC.Unit.Module.Deps
( Dependencies(dep_direct_mods
, dep_direct_pkgs
, dep_sig_mods
, dep_trusted_pkgs
, dep_orphs
, dep_plugin_pkgs
, dep_finsts
, dep_boot_mods
, Dependencies)
, dep_orphs_update
, dep_finsts_update
, mkDependencies
, noDependencies
, pprDeps
, Usage (..)
, HomeModImport (..)
, HomeModImportedAvails (..)
, ImportAvails (..)
, IfaceImportLevel(..)
, tcImportLevel
)
where
import GHC.Prelude
import GHC.Data.FastString
import GHC.Types.Avail
import GHC.Types.SafeHaskell
import GHC.Types.Name
import GHC.Types.Basic
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
import Control.DeepSeq
import GHC.Types.Name.Set
data Dependencies = Deps
{ Dependencies
-> Set (IfaceImportLevel, UnitId, GenWithIsBoot ModuleName)
dep_direct_mods_ :: Set (IfaceImportLevel, UnitId, ModuleNameWithIsBoot)
, Dependencies -> Set (IfaceImportLevel, UnitId)
dep_direct_pkgs_ :: Set (IfaceImportLevel, 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 )
pattern Dependencies :: Set (IfaceImportLevel, UnitId, ModuleNameWithIsBoot)
-> Set (IfaceImportLevel, UnitId)
-> Set UnitId
-> [ModuleName]
-> Set UnitId
-> Set (UnitId, ModuleNameWithIsBoot)
-> [Module]
-> [Module]
-> Dependencies
pattern $mDependencies :: forall {r}.
Dependencies
-> (Set (IfaceImportLevel, UnitId, GenWithIsBoot ModuleName)
-> Set (IfaceImportLevel, UnitId)
-> Set UnitId
-> [ModuleName]
-> Set UnitId
-> Set (UnitId, GenWithIsBoot ModuleName)
-> [Module]
-> [Module]
-> r)
-> ((# #) -> r)
-> r
Dependencies {Dependencies
-> Set (IfaceImportLevel, UnitId, GenWithIsBoot ModuleName)
dep_direct_mods, Dependencies -> Set (IfaceImportLevel, UnitId)
dep_direct_pkgs, Dependencies -> Set UnitId
dep_plugin_pkgs, Dependencies -> [ModuleName]
dep_sig_mods, Dependencies -> Set UnitId
dep_trusted_pkgs, Dependencies -> Set (UnitId, GenWithIsBoot ModuleName)
dep_boot_mods, Dependencies -> [Module]
dep_orphs, Dependencies -> [Module]
dep_finsts}
<- Deps {dep_direct_mods_ = dep_direct_mods
, dep_direct_pkgs_ = dep_direct_pkgs
, dep_plugin_pkgs_ = dep_plugin_pkgs
, dep_sig_mods_ = dep_sig_mods
, dep_trusted_pkgs_ = dep_trusted_pkgs
, dep_boot_mods_ = dep_boot_mods
, dep_orphs_ = dep_orphs
, dep_finsts_ = dep_finsts}
{-# COMPLETE Dependencies #-}
instance NFData Dependencies where
rnf :: Dependencies -> ()
rnf (Deps Set (IfaceImportLevel, UnitId, GenWithIsBoot ModuleName)
dmods Set (IfaceImportLevel, UnitId)
dpkgs Set UnitId
ppkgs [ModuleName]
hsigms Set UnitId
tps Set (UnitId, GenWithIsBoot ModuleName)
bmods [Module]
orphs [Module]
finsts)
= Set (IfaceImportLevel, UnitId, GenWithIsBoot ModuleName) -> ()
forall a. NFData a => a -> ()
rnf Set (IfaceImportLevel, UnitId, GenWithIsBoot ModuleName)
dmods
() -> () -> ()
forall a b. a -> b -> b
`seq` Set (IfaceImportLevel, UnitId) -> ()
forall a. NFData a => a -> ()
rnf Set (IfaceImportLevel, UnitId)
dpkgs
() -> () -> ()
forall a b. a -> b -> b
`seq` Set UnitId -> ()
forall a. NFData a => a -> ()
rnf Set UnitId
ppkgs
() -> () -> ()
forall a b. a -> b -> b
`seq` [ModuleName] -> ()
forall a. NFData a => a -> ()
rnf [ModuleName]
hsigms
() -> () -> ()
forall a b. a -> b -> b
`seq` Set UnitId -> ()
forall a. NFData a => a -> ()
rnf Set UnitId
tps
() -> () -> ()
forall a b. a -> b -> b
`seq` Set (UnitId, GenWithIsBoot ModuleName) -> ()
forall a. NFData a => a -> ()
rnf Set (UnitId, GenWithIsBoot ModuleName)
bmods
() -> () -> ()
forall a b. a -> b -> b
`seq` [Module] -> ()
forall a. NFData a => a -> ()
rnf [Module]
orphs
() -> () -> ()
forall a b. a -> b -> b
`seq` [Module] -> ()
forall a. NFData a => a -> ()
rnf [Module]
finsts
() -> () -> ()
forall a b. a -> b -> b
`seq` ()
newtype IfaceImportLevel = IfaceImportLevel ImportLevel
deriving (IfaceImportLevel -> IfaceImportLevel -> Bool
(IfaceImportLevel -> IfaceImportLevel -> Bool)
-> (IfaceImportLevel -> IfaceImportLevel -> Bool)
-> Eq IfaceImportLevel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IfaceImportLevel -> IfaceImportLevel -> Bool
== :: IfaceImportLevel -> IfaceImportLevel -> Bool
$c/= :: IfaceImportLevel -> IfaceImportLevel -> Bool
/= :: IfaceImportLevel -> IfaceImportLevel -> Bool
Eq, Eq IfaceImportLevel
Eq IfaceImportLevel =>
(IfaceImportLevel -> IfaceImportLevel -> Ordering)
-> (IfaceImportLevel -> IfaceImportLevel -> Bool)
-> (IfaceImportLevel -> IfaceImportLevel -> Bool)
-> (IfaceImportLevel -> IfaceImportLevel -> Bool)
-> (IfaceImportLevel -> IfaceImportLevel -> Bool)
-> (IfaceImportLevel -> IfaceImportLevel -> IfaceImportLevel)
-> (IfaceImportLevel -> IfaceImportLevel -> IfaceImportLevel)
-> Ord IfaceImportLevel
IfaceImportLevel -> IfaceImportLevel -> Bool
IfaceImportLevel -> IfaceImportLevel -> Ordering
IfaceImportLevel -> IfaceImportLevel -> IfaceImportLevel
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: IfaceImportLevel -> IfaceImportLevel -> Ordering
compare :: IfaceImportLevel -> IfaceImportLevel -> Ordering
$c< :: IfaceImportLevel -> IfaceImportLevel -> Bool
< :: IfaceImportLevel -> IfaceImportLevel -> Bool
$c<= :: IfaceImportLevel -> IfaceImportLevel -> Bool
<= :: IfaceImportLevel -> IfaceImportLevel -> Bool
$c> :: IfaceImportLevel -> IfaceImportLevel -> Bool
> :: IfaceImportLevel -> IfaceImportLevel -> Bool
$c>= :: IfaceImportLevel -> IfaceImportLevel -> Bool
>= :: IfaceImportLevel -> IfaceImportLevel -> Bool
$cmax :: IfaceImportLevel -> IfaceImportLevel -> IfaceImportLevel
max :: IfaceImportLevel -> IfaceImportLevel -> IfaceImportLevel
$cmin :: IfaceImportLevel -> IfaceImportLevel -> IfaceImportLevel
min :: IfaceImportLevel -> IfaceImportLevel -> IfaceImportLevel
Ord)
deriving ReadBinHandle -> IO IfaceImportLevel
WriteBinHandle -> IfaceImportLevel -> IO ()
WriteBinHandle -> IfaceImportLevel -> IO (Bin IfaceImportLevel)
(WriteBinHandle -> IfaceImportLevel -> IO ())
-> (WriteBinHandle
-> IfaceImportLevel -> IO (Bin IfaceImportLevel))
-> (ReadBinHandle -> IO IfaceImportLevel)
-> Binary IfaceImportLevel
forall a.
(WriteBinHandle -> a -> IO ())
-> (WriteBinHandle -> a -> IO (Bin a))
-> (ReadBinHandle -> IO a)
-> Binary a
$cput_ :: WriteBinHandle -> IfaceImportLevel -> IO ()
put_ :: WriteBinHandle -> IfaceImportLevel -> IO ()
$cput :: WriteBinHandle -> IfaceImportLevel -> IO (Bin IfaceImportLevel)
put :: WriteBinHandle -> IfaceImportLevel -> IO (Bin IfaceImportLevel)
$cget :: ReadBinHandle -> IO IfaceImportLevel
get :: ReadBinHandle -> IO IfaceImportLevel
Binary via EnumBinary ImportLevel
tcImportLevel :: IfaceImportLevel -> ImportLevel
tcImportLevel :: IfaceImportLevel -> ImportLevel
tcImportLevel (IfaceImportLevel ImportLevel
lvl) = ImportLevel
lvl
instance NFData IfaceImportLevel where
rnf :: IfaceImportLevel -> ()
rnf (IfaceImportLevel ImportLevel
lvl) = case ImportLevel
lvl of
ImportLevel
NormalLevel -> ()
ImportLevel
QuoteLevel -> ()
ImportLevel
SpliceLevel -> ()
instance Outputable IfaceImportLevel where
ppr :: IfaceImportLevel -> SDoc
ppr (IfaceImportLevel ImportLevel
lvl) = ImportLevel -> SDoc
forall a. Outputable a => a -> SDoc
ppr ImportLevel
lvl
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 (Set ImportLevel, GenWithIsBoot ModuleName)
all_direct_mods = ((Set ImportLevel, InstalledModule)
-> InstalledModuleEnv (Set ImportLevel, GenWithIsBoot ModuleName)
-> InstalledModuleEnv (Set ImportLevel, GenWithIsBoot ModuleName))
-> InstalledModuleEnv (Set ImportLevel, GenWithIsBoot ModuleName)
-> [(Set ImportLevel, InstalledModule)]
-> InstalledModuleEnv (Set ImportLevel, 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 (\(Set ImportLevel
s, InstalledModule
mn) InstalledModuleEnv (Set ImportLevel, GenWithIsBoot ModuleName)
m -> InstalledModuleEnv (Set ImportLevel, GenWithIsBoot ModuleName)
-> InstalledModule
-> (Set ImportLevel, GenWithIsBoot ModuleName)
-> InstalledModuleEnv (Set ImportLevel, GenWithIsBoot ModuleName)
forall a.
InstalledModuleEnv a
-> InstalledModule -> a -> InstalledModuleEnv a
extendInstalledModuleEnv InstalledModuleEnv (Set ImportLevel, GenWithIsBoot ModuleName)
m InstalledModule
mn (Set ImportLevel
s, (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 (Set ImportLevel, GenWithIsBoot ModuleName)
imp_direct_dep_mods ImportAvails
imports)
((Module -> (Set ImportLevel, InstalledModule))
-> [Module] -> [(Set ImportLevel, InstalledModule)]
forall a b. (a -> b) -> [a] -> [b]
map ((Module -> InstalledModule)
-> (Set ImportLevel, Module) -> (Set ImportLevel, InstalledModule)
forall a b.
(a -> b) -> (Set ImportLevel, a) -> (Set ImportLevel, b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((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) ((Set ImportLevel, Module) -> (Set ImportLevel, InstalledModule))
-> (Module -> (Set ImportLevel, Module))
-> Module
-> (Set ImportLevel, InstalledModule)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ImportLevel -> Set ImportLevel
forall a. a -> Set a
Set.singleton ImportLevel
SpliceLevel,)) [Module]
home_plugins)
modDepsElts_source :: Ord a => InstalledModuleEnv a -> Set.Set (InstalledModule, a)
modDepsElts_source :: forall a. Ord a => InstalledModuleEnv a -> Set (InstalledModule, a)
modDepsElts_source = [(InstalledModule, a)] -> Set (InstalledModule, a)
forall a. Ord a => [a] -> Set a
Set.fromList ([(InstalledModule, a)] -> Set (InstalledModule, a))
-> (InstalledModuleEnv a -> [(InstalledModule, a)])
-> InstalledModuleEnv a
-> Set (InstalledModule, a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InstalledModuleEnv a -> [(InstalledModule, a)]
forall a. InstalledModuleEnv a -> [(InstalledModule, a)]
installedModuleEnvElts
modDepsElts :: Ord a => InstalledModuleEnv (Set.Set ImportLevel, a) -> Set.Set (IfaceImportLevel, UnitId, a)
modDepsElts :: forall a.
Ord a =>
InstalledModuleEnv (Set ImportLevel, a)
-> Set (IfaceImportLevel, UnitId, a)
modDepsElts InstalledModuleEnv (Set ImportLevel, a)
e = [(IfaceImportLevel, UnitId, a)]
-> Set (IfaceImportLevel, UnitId, a)
forall a. Ord a => [a] -> Set a
Set.fromList [ (ImportLevel -> IfaceImportLevel
IfaceImportLevel ImportLevel
s, InstalledModule -> UnitId
forall unit. GenModule unit -> unit
moduleUnit InstalledModule
im, a
a) | (InstalledModule
im, (Set ImportLevel
ss,a
a)) <- InstalledModuleEnv (Set ImportLevel, a)
-> [(InstalledModule, (Set ImportLevel, a))]
forall a. InstalledModuleEnv a -> [(InstalledModule, a)]
installedModuleEnvElts InstalledModuleEnv (Set ImportLevel, a)
e, ImportLevel
s <- Set ImportLevel -> [ImportLevel]
forall a. Set a -> [a]
Set.toList Set ImportLevel
ss]
direct_mods :: Set (IfaceImportLevel, UnitId, GenWithIsBoot ModuleName)
direct_mods = InstalledModuleEnv (Set ImportLevel, GenWithIsBoot ModuleName)
-> Set (IfaceImportLevel, UnitId, GenWithIsBoot ModuleName)
forall a.
Ord a =>
InstalledModuleEnv (Set ImportLevel, a)
-> Set (IfaceImportLevel, UnitId, a)
modDepsElts (InstalledModuleEnv (Set ImportLevel, GenWithIsBoot ModuleName)
-> InstalledModule
-> InstalledModuleEnv (Set ImportLevel, GenWithIsBoot ModuleName)
forall a.
InstalledModuleEnv a -> InstalledModule -> InstalledModuleEnv a
delInstalledModuleEnv InstalledModuleEnv (Set ImportLevel, 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 (IfaceImportLevel, UnitId)
direct_pkgs = ((ImportLevel, UnitId) -> (IfaceImportLevel, UnitId))
-> Set (ImportLevel, UnitId) -> Set (IfaceImportLevel, UnitId)
forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map (\(ImportLevel
lvl, UnitId
uid) -> (ImportLevel -> IfaceImportLevel
IfaceImportLevel ImportLevel
lvl, UnitId
uid)) (ImportAvails -> Set (ImportLevel, 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)
forall a. Ord a => InstalledModuleEnv a -> Set (InstalledModule, a)
modDepsElts_source (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 (IfaceImportLevel, UnitId, GenWithIsBoot ModuleName)
dep_direct_mods_ = Set (IfaceImportLevel, UnitId, GenWithIsBoot ModuleName)
direct_mods
, dep_direct_pkgs_ :: Set (IfaceImportLevel, UnitId)
dep_direct_pkgs_ = Set (IfaceImportLevel, 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
r <- [Module] -> m [Module]
f (Dependencies -> [Module]
dep_orphs Dependencies
deps)
pure (deps { dep_orphs_ = sortBy stableModuleCmp 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
r <- [Module] -> m [Module]
f (Dependencies -> [Module]
dep_finsts Dependencies
deps)
pure (deps { dep_finsts_ = sortBy stableModuleCmp r })
instance Binary Dependencies where
put_ :: WriteBinHandle -> Dependencies -> IO ()
put_ WriteBinHandle
bh Dependencies
deps = do WriteBinHandle
-> Set (IfaceImportLevel, UnitId, GenWithIsBoot ModuleName)
-> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Dependencies
-> Set (IfaceImportLevel, UnitId, GenWithIsBoot ModuleName)
dep_direct_mods Dependencies
deps)
WriteBinHandle -> Set (IfaceImportLevel, UnitId) -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Dependencies -> Set (IfaceImportLevel, UnitId)
dep_direct_pkgs Dependencies
deps)
WriteBinHandle -> Set UnitId -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Dependencies -> Set UnitId
dep_plugin_pkgs Dependencies
deps)
WriteBinHandle -> Set UnitId -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Dependencies -> Set UnitId
dep_trusted_pkgs Dependencies
deps)
WriteBinHandle -> [ModuleName] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Dependencies -> [ModuleName]
dep_sig_mods Dependencies
deps)
WriteBinHandle -> Set (UnitId, GenWithIsBoot ModuleName) -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Dependencies -> Set (UnitId, GenWithIsBoot ModuleName)
dep_boot_mods Dependencies
deps)
WriteBinHandle -> [Module] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Dependencies -> [Module]
dep_orphs Dependencies
deps)
WriteBinHandle -> [Module] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Dependencies -> [Module]
dep_finsts Dependencies
deps)
get :: ReadBinHandle -> IO Dependencies
get ReadBinHandle
bh = do dms <- ReadBinHandle
-> IO (Set (IfaceImportLevel, UnitId, GenWithIsBoot ModuleName))
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
dps <- get bh
plugin_pkgs <- get bh
tps <- get bh
hsigms <- get bh
sms <- get bh
os <- get bh
fis <- get bh
return (Deps { dep_direct_mods_ = dms
, dep_direct_pkgs_ = dps
, dep_plugin_pkgs_ = plugin_pkgs
, dep_sig_mods_ = hsigms
, dep_boot_mods_ = sms
, dep_trusted_pkgs_ = tps
, dep_orphs_ = os,
dep_finsts_ = fis })
noDependencies :: Dependencies
noDependencies :: Dependencies
noDependencies = Deps
{ dep_direct_mods_ :: Set (IfaceImportLevel, UnitId, GenWithIsBoot ModuleName)
dep_direct_mods_ = Set (IfaceImportLevel, UnitId, GenWithIsBoot ModuleName)
forall a. Set a
Set.empty
, dep_direct_pkgs_ :: Set (IfaceImportLevel, UnitId)
dep_direct_pkgs_ = Set (IfaceImportLevel, 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 (IfaceImportLevel, UnitId, GenWithIsBoot ModuleName)
dep_direct_mods_ = Set (IfaceImportLevel, 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 (IfaceImportLevel, UnitId)
dep_direct_pkgs_ = Set (IfaceImportLevel, 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
forall doc. IsDoc doc => [doc] -> doc
vcat [String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"direct module dependencies:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> ((IfaceImportLevel, UnitId, GenWithIsBoot ModuleName) -> SDoc)
-> Set (IfaceImportLevel, UnitId, GenWithIsBoot ModuleName) -> SDoc
forall a. Outputable a => (a -> SDoc) -> Set a -> SDoc
ppr_set (IfaceImportLevel, UnitId, GenWithIsBoot ModuleName) -> SDoc
forall {a} {a} {a}.
(Outputable a, Outputable a, Outputable a) =>
(a, a, GenWithIsBoot a) -> SDoc
ppr_mod Set (IfaceImportLevel, UnitId, GenWithIsBoot ModuleName)
dmods,
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"boot module dependencies:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> ((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
forall doc. IsLine doc => String -> doc
text String
"direct package dependencies:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> ((IfaceImportLevel, UnitId) -> SDoc)
-> Set (IfaceImportLevel, UnitId) -> SDoc
forall a. Outputable a => (a -> SDoc) -> Set a -> SDoc
ppr_set (IfaceImportLevel, UnitId) -> SDoc
forall a. Outputable a => a -> SDoc
ppr Set (IfaceImportLevel, UnitId)
pkgs,
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"plugin package dependencies:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (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
forall doc. IsOutput doc => doc
empty
else String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"trusted package dependencies:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (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
forall doc. IsLine doc => String -> doc
text String
"orphans:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
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
forall doc. IsLine doc => String -> doc
text String
"family instance modules:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
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, a, GenWithIsBoot a) -> SDoc
ppr_mod (a
_, a
uid, (GWIB a
mod IsBootInterface
IsBoot)) = a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
uid SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc
forall doc. IsLine doc => doc
colon SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
mod SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"[boot]"
ppr_mod (a
lvl, a
uid, (GWIB a
mod IsBootInterface
NotBoot)) = a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
lvl SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
uid SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc
forall doc. IsLine doc => doc
colon SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> 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
forall doc. IsLine doc => [doc] -> doc
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,
Usage -> UnitId
usg_unit_id :: UnitId,
usg_mod_hash :: Fingerprint,
Usage -> [(OccName, Fingerprint)]
usg_entities :: [(OccName,Fingerprint)],
Usage -> Maybe HomeModImport
usg_exports :: Maybe HomeModImport,
usg_safe :: IsSafeImport
}
| UsageFile {
Usage -> FastString
usg_file_path :: FastString,
Usage -> Fingerprint
usg_file_hash :: Fingerprint,
Usage -> Maybe String
usg_file_label :: Maybe String
}
| UsageHomeModuleInterface {
usg_mod_name :: ModuleName
, usg_unit_id :: UnitId
, 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 NFData Usage where
rnf :: Usage -> ()
rnf (UsagePackageModule Module
mod Fingerprint
hash Bool
safe) = Module -> ()
forall a. NFData a => a -> ()
rnf Module
mod () -> () -> ()
forall a b. a -> b -> b
`seq` Fingerprint -> ()
forall a. NFData a => a -> ()
rnf Fingerprint
hash () -> () -> ()
forall a b. a -> b -> b
`seq` Bool -> ()
forall a. NFData a => a -> ()
rnf Bool
safe () -> () -> ()
forall a b. a -> b -> b
`seq` ()
rnf (UsageHomeModule ModuleName
mod UnitId
uid Fingerprint
hash [(OccName, Fingerprint)]
entities Maybe HomeModImport
exports Bool
safe) = ModuleName -> ()
forall a. NFData a => a -> ()
rnf ModuleName
mod () -> () -> ()
forall a b. a -> b -> b
`seq` UnitId -> ()
forall a. NFData a => a -> ()
rnf UnitId
uid () -> () -> ()
forall a b. a -> b -> b
`seq` Fingerprint -> ()
forall a. NFData a => a -> ()
rnf Fingerprint
hash () -> () -> ()
forall a b. a -> b -> b
`seq` [(OccName, Fingerprint)] -> ()
forall a. NFData a => a -> ()
rnf [(OccName, Fingerprint)]
entities () -> () -> ()
forall a b. a -> b -> b
`seq` Maybe HomeModImport -> ()
forall a. NFData a => a -> ()
rnf Maybe HomeModImport
exports () -> () -> ()
forall a b. a -> b -> b
`seq` Bool -> ()
forall a. NFData a => a -> ()
rnf Bool
safe () -> () -> ()
forall a b. a -> b -> b
`seq` ()
rnf (UsageFile FastString
file Fingerprint
hash Maybe String
label) = FastString -> ()
forall a. NFData a => a -> ()
rnf FastString
file () -> () -> ()
forall a b. a -> b -> b
`seq` Fingerprint -> ()
forall a. NFData a => a -> ()
rnf Fingerprint
hash () -> () -> ()
forall a b. a -> b -> b
`seq` Maybe String -> ()
forall a. NFData a => a -> ()
rnf Maybe String
label () -> () -> ()
forall a b. a -> b -> b
`seq` ()
rnf (UsageMergedRequirement Module
mod Fingerprint
hash) = Module -> ()
forall a. NFData a => a -> ()
rnf Module
mod () -> () -> ()
forall a b. a -> b -> b
`seq` Fingerprint -> ()
forall a. NFData a => a -> ()
rnf Fingerprint
hash () -> () -> ()
forall a b. a -> b -> b
`seq` ()
rnf (UsageHomeModuleInterface ModuleName
mod UnitId
uid Fingerprint
hash) = ModuleName -> ()
forall a. NFData a => a -> ()
rnf ModuleName
mod () -> () -> ()
forall a b. a -> b -> b
`seq` UnitId -> ()
forall a. NFData a => a -> ()
rnf UnitId
uid () -> () -> ()
forall a b. a -> b -> b
`seq` Fingerprint -> ()
forall a. NFData a => a -> ()
rnf Fingerprint
hash () -> () -> ()
forall a b. a -> b -> b
`seq` ()
instance Binary Usage where
put_ :: WriteBinHandle -> Usage -> IO ()
put_ WriteBinHandle
bh usg :: Usage
usg@UsagePackageModule{} = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
0
WriteBinHandle -> Module -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Usage -> Module
usg_mod Usage
usg)
WriteBinHandle -> Fingerprint -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Usage -> Fingerprint
usg_mod_hash Usage
usg)
WriteBinHandle -> Bool -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Usage -> Bool
usg_safe Usage
usg)
put_ WriteBinHandle
bh usg :: Usage
usg@UsageHomeModule{} = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
1
WriteBinHandle -> ModuleName -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Usage -> ModuleName
usg_mod_name Usage
usg)
WriteBinHandle -> UnitId -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Usage -> UnitId
usg_unit_id Usage
usg)
WriteBinHandle -> Fingerprint -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Usage -> Fingerprint
usg_mod_hash Usage
usg)
WriteBinHandle -> Maybe HomeModImport -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Usage -> Maybe HomeModImport
usg_exports Usage
usg)
WriteBinHandle -> [(OccName, Fingerprint)] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Usage -> [(OccName, Fingerprint)]
usg_entities Usage
usg)
WriteBinHandle -> Bool -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Usage -> Bool
usg_safe Usage
usg)
put_ WriteBinHandle
bh usg :: Usage
usg@UsageFile{} = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
2
WriteBinHandle -> FastString -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Usage -> FastString
usg_file_path Usage
usg)
WriteBinHandle -> Fingerprint -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Usage -> Fingerprint
usg_file_hash Usage
usg)
WriteBinHandle -> Maybe String -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Usage -> Maybe String
usg_file_label Usage
usg)
put_ WriteBinHandle
bh usg :: Usage
usg@UsageMergedRequirement{} = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
3
WriteBinHandle -> Module -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Usage -> Module
usg_mod Usage
usg)
WriteBinHandle -> Fingerprint -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Usage -> Fingerprint
usg_mod_hash Usage
usg)
put_ WriteBinHandle
bh usg :: Usage
usg@UsageHomeModuleInterface{} = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
4
WriteBinHandle -> ModuleName -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Usage -> ModuleName
usg_mod_name Usage
usg)
WriteBinHandle -> UnitId -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Usage -> UnitId
usg_unit_id Usage
usg)
WriteBinHandle -> Fingerprint -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (Usage -> Fingerprint
usg_iface_hash Usage
usg)
get :: ReadBinHandle -> IO Usage
get ReadBinHandle
bh = do
h <- ReadBinHandle -> IO Word8
getByte ReadBinHandle
bh
case h of
Word8
0 -> do
nm <- ReadBinHandle -> IO Module
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
mod <- get bh
safe <- get bh
return UsagePackageModule { usg_mod = nm, usg_mod_hash = mod, usg_safe = safe }
Word8
1 -> do
nm <- ReadBinHandle -> IO ModuleName
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
uid <- 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_unit_id = uid,
usg_exports = exps, usg_entities = ents, usg_safe = safe }
Word8
2 -> do
fp <- ReadBinHandle -> IO FastString
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
hash <- get bh
label <- get bh
return UsageFile { usg_file_path = fp, usg_file_hash = hash, usg_file_label = label }
Word8
3 -> do
mod <- ReadBinHandle -> IO Module
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
hash <- get bh
return UsageMergedRequirement { usg_mod = mod, usg_mod_hash = hash }
Word8
4 -> do
mod <- ReadBinHandle -> IO ModuleName
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
uid <- get bh
hash <- get bh
return UsageHomeModuleInterface { usg_mod_name = mod, usg_unit_id = uid, usg_iface_hash = 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 HomeModImport
= HomeModImport
{ HomeModImport -> Fingerprint
hmiu_orphanLikeHash :: Fingerprint
, HomeModImport -> HomeModImportedAvails
hmiu_importedAvails :: HomeModImportedAvails
}
deriving stock HomeModImport -> HomeModImport -> Bool
(HomeModImport -> HomeModImport -> Bool)
-> (HomeModImport -> HomeModImport -> Bool) -> Eq HomeModImport
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HomeModImport -> HomeModImport -> Bool
== :: HomeModImport -> HomeModImport -> Bool
$c/= :: HomeModImport -> HomeModImport -> Bool
/= :: HomeModImport -> HomeModImport -> Bool
Eq
data HomeModImportedAvails
= HMIA_Explicit
{ HomeModImportedAvails -> DetOrdAvails
hmia_imported_avails :: DetOrdAvails
, HomeModImportedAvails -> NameSet
hmia_parents_with_implicits :: NameSet
}
| HMIA_Implicit
{ HomeModImportedAvails -> Fingerprint
hmia_exportedAvailsHash :: Fingerprint
}
deriving stock HomeModImportedAvails -> HomeModImportedAvails -> Bool
(HomeModImportedAvails -> HomeModImportedAvails -> Bool)
-> (HomeModImportedAvails -> HomeModImportedAvails -> Bool)
-> Eq HomeModImportedAvails
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HomeModImportedAvails -> HomeModImportedAvails -> Bool
== :: HomeModImportedAvails -> HomeModImportedAvails -> Bool
$c/= :: HomeModImportedAvails -> HomeModImportedAvails -> Bool
/= :: HomeModImportedAvails -> HomeModImportedAvails -> Bool
Eq
instance Outputable HomeModImport where
ppr :: HomeModImport -> SDoc
ppr (HomeModImport Fingerprint
orphan_like HomeModImportedAvails
imp_avails) =
SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
braces (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"orphan_like:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Fingerprint -> SDoc
forall a. Outputable a => a -> SDoc
ppr Fingerprint
orphan_like SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
", imported avails:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> HomeModImportedAvails -> SDoc
forall a. Outputable a => a -> SDoc
ppr HomeModImportedAvails
imp_avails)
instance Outputable HomeModImportedAvails where
ppr :: HomeModImportedAvails -> SDoc
ppr (HMIA_Explicit DetOrdAvails
avails NameSet
implicit_parents) =
SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
braces (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"explicit:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> DetOrdAvails -> SDoc
forall a. Outputable a => a -> SDoc
ppr DetOrdAvails
avails SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
", implicit_parents:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> NameSet -> SDoc
forall a. Outputable a => a -> SDoc
ppr NameSet
implicit_parents)
ppr (HMIA_Implicit Fingerprint
hash) = SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
braces (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"implicit:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Fingerprint -> SDoc
forall a. Outputable a => a -> SDoc
ppr Fingerprint
hash)
instance NFData HomeModImport where
rnf :: HomeModImport -> ()
rnf (HomeModImport Fingerprint
a HomeModImportedAvails
b) = Fingerprint -> ()
forall a. NFData a => a -> ()
rnf Fingerprint
a () -> () -> ()
forall a b. a -> b -> b
`seq` HomeModImportedAvails -> ()
forall a. NFData a => a -> ()
rnf HomeModImportedAvails
b () -> () -> ()
forall a b. a -> b -> b
`seq` ()
instance NFData HomeModImportedAvails where
rnf :: HomeModImportedAvails -> ()
rnf (HMIA_Explicit DetOrdAvails
avails NameSet
implicit_parents) = DetOrdAvails -> ()
forall a. NFData a => a -> ()
rnf DetOrdAvails
avails () -> () -> ()
forall a b. a -> b -> b
`seq` NameSet -> ()
forall a. NFData a => a -> ()
rnf NameSet
implicit_parents
rnf (HMIA_Implicit Fingerprint
hash) = Fingerprint -> ()
forall a. NFData a => a -> ()
rnf Fingerprint
hash
instance Binary HomeModImport where
put_ :: WriteBinHandle -> HomeModImport -> IO ()
put_ WriteBinHandle
bh (HomeModImport Fingerprint
a HomeModImportedAvails
b) = WriteBinHandle -> Fingerprint -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Fingerprint
a IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> HomeModImportedAvails -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh HomeModImportedAvails
b
get :: ReadBinHandle -> IO HomeModImport
get ReadBinHandle
bh = do
a <- ReadBinHandle -> IO Fingerprint
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
b <- get bh
return $ HomeModImport a b
instance Binary HomeModImportedAvails where
put_ :: WriteBinHandle -> HomeModImportedAvails -> IO ()
put_ WriteBinHandle
bh (HMIA_Explicit DetOrdAvails
avails NameSet
implicit_parents) =
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
0 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> DetOrdAvails -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh DetOrdAvails
avails IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> [Name] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (NameSet -> [Name]
nameSetElemsStable NameSet
implicit_parents)
put_ WriteBinHandle
bh (HMIA_Implicit Fingerprint
hash ) = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
1 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> Fingerprint -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Fingerprint
hash
get :: ReadBinHandle -> IO HomeModImportedAvails
get ReadBinHandle
bh = do
tag <- ReadBinHandle -> IO Word8
getByte ReadBinHandle
bh
case tag of
Word8
0 -> DetOrdAvails -> NameSet -> HomeModImportedAvails
HMIA_Explicit (DetOrdAvails -> NameSet -> HomeModImportedAvails)
-> IO DetOrdAvails -> IO (NameSet -> HomeModImportedAvails)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO DetOrdAvails
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh IO (NameSet -> HomeModImportedAvails)
-> IO NameSet -> IO HomeModImportedAvails
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ([Name] -> NameSet
mkNameSet ([Name] -> NameSet) -> IO [Name] -> IO NameSet
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO [Name]
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh)
Word8
1 -> Fingerprint -> HomeModImportedAvails
HMIA_Implicit (Fingerprint -> HomeModImportedAvails)
-> IO Fingerprint -> IO HomeModImportedAvails
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO Fingerprint
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
Word8
_ -> String -> IO HomeModImportedAvails
forall a. HasCallStack => String -> a
error (String
"Binary.get(HomeModImportedAvails): " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Word8 -> String
forall a. Show a => a -> String
show Word8
tag)
data ImportAvails
= ImportAvails {
ImportAvails -> ImportedMods
imp_mods :: ImportedMods,
ImportAvails
-> InstalledModuleEnv (Set ImportLevel, GenWithIsBoot ModuleName)
imp_direct_dep_mods :: InstalledModuleEnv (Set.Set ImportLevel, ModuleNameWithIsBoot),
ImportAvails -> Set (ImportLevel, UnitId)
imp_dep_direct_pkgs :: Set (ImportLevel, 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]
}