module GHC.Unit.Home
( GenHomeUnit (..)
, HomeUnit
, homeUnitId
, homeUnitInstantiations
, homeUnitInstanceOf
, homeUnitInstanceOfMaybe
, homeUnitAsUnit
, homeUnitMap
, isHomeUnitIndefinite
, isHomeUnitDefinite
, isHomeUnitInstantiating
, isHomeUnit
, isHomeUnitId
, isHomeUnitInstanceOf
, isHomeModule
, isHomeInstalledModule
, notHomeModule
, notHomeModuleMaybe
, notHomeInstalledModule
, notHomeInstalledModuleMaybe
, mkHomeModule
, mkHomeInstalledModule
, homeModuleInstantiation
, homeModuleNameInstantiation
)
where
import GHC.Prelude
import GHC.Unit.Types
import GHC.Unit.Module.Name
import Data.Maybe
data GenHomeUnit u
= DefiniteHomeUnit UnitId (Maybe (u, GenInstantiations u))
| IndefiniteHomeUnit UnitId (GenInstantiations u)
type HomeUnit = GenHomeUnit UnitId
homeUnitId :: GenHomeUnit u -> UnitId
homeUnitId :: forall u. GenHomeUnit u -> UnitId
homeUnitId (DefiniteHomeUnit UnitId
u Maybe (u, GenInstantiations u)
_) = UnitId
u
homeUnitId (IndefiniteHomeUnit UnitId
u GenInstantiations u
_) = UnitId
u
homeUnitInstantiations :: GenHomeUnit u -> GenInstantiations u
homeUnitInstantiations :: forall u. GenHomeUnit u -> GenInstantiations u
homeUnitInstantiations (DefiniteHomeUnit UnitId
_ Maybe (u, GenInstantiations u)
Nothing) = []
homeUnitInstantiations (DefiniteHomeUnit UnitId
_ (Just (u
_,GenInstantiations u
is))) = GenInstantiations u
is
homeUnitInstantiations (IndefiniteHomeUnit UnitId
_ GenInstantiations u
is) = GenInstantiations u
is
homeUnitInstanceOf :: HomeUnit -> UnitId
homeUnitInstanceOf :: HomeUnit -> UnitId
homeUnitInstanceOf HomeUnit
h = UnitId -> Maybe UnitId -> UnitId
forall a. a -> Maybe a -> a
fromMaybe (HomeUnit -> UnitId
forall u. GenHomeUnit u -> UnitId
homeUnitId HomeUnit
h) (HomeUnit -> Maybe UnitId
forall u. GenHomeUnit u -> Maybe u
homeUnitInstanceOfMaybe HomeUnit
h)
homeUnitInstanceOfMaybe :: GenHomeUnit u -> Maybe u
homeUnitInstanceOfMaybe :: forall u. GenHomeUnit u -> Maybe u
homeUnitInstanceOfMaybe (DefiniteHomeUnit UnitId
_ (Just (u
u,GenInstantiations u
_))) = u -> Maybe u
forall a. a -> Maybe a
Just u
u
homeUnitInstanceOfMaybe GenHomeUnit u
_ = Maybe u
forall a. Maybe a
Nothing
homeUnitAsUnit :: HomeUnit -> Unit
homeUnitAsUnit :: HomeUnit -> Unit
homeUnitAsUnit (DefiniteHomeUnit UnitId
u Maybe (UnitId, GenInstantiations UnitId)
_) = Definite UnitId -> Unit
forall uid. Definite uid -> GenUnit uid
RealUnit (UnitId -> Definite UnitId
forall unit. unit -> Definite unit
Definite UnitId
u)
homeUnitAsUnit (IndefiniteHomeUnit UnitId
u GenInstantiations UnitId
is) = Indefinite UnitId -> GenInstantiations UnitId -> Unit
forall u.
IsUnitId u =>
Indefinite u -> [(ModuleName, GenModule (GenUnit u))] -> GenUnit u
mkVirtUnit (UnitId -> Indefinite UnitId
forall unit. unit -> Indefinite unit
Indefinite UnitId
u) GenInstantiations UnitId
is
homeUnitMap :: IsUnitId v => (u -> v) -> GenHomeUnit u -> GenHomeUnit v
homeUnitMap :: forall v u.
IsUnitId v =>
(u -> v) -> GenHomeUnit u -> GenHomeUnit v
homeUnitMap u -> v
_ (DefiniteHomeUnit UnitId
u Maybe (u, GenInstantiations u)
Nothing) = UnitId -> Maybe (v, GenInstantiations v) -> GenHomeUnit v
forall u. UnitId -> Maybe (u, GenInstantiations u) -> GenHomeUnit u
DefiniteHomeUnit UnitId
u Maybe (v, GenInstantiations v)
forall a. Maybe a
Nothing
homeUnitMap u -> v
f (DefiniteHomeUnit UnitId
u (Just (u
i,GenInstantiations u
is))) = UnitId -> Maybe (v, GenInstantiations v) -> GenHomeUnit v
forall u. UnitId -> Maybe (u, GenInstantiations u) -> GenHomeUnit u
DefiniteHomeUnit UnitId
u ((v, GenInstantiations v) -> Maybe (v, GenInstantiations v)
forall a. a -> Maybe a
Just (u -> v
f u
i, (u -> v) -> GenInstantiations u -> GenInstantiations v
forall v u.
IsUnitId v =>
(u -> v) -> GenInstantiations u -> GenInstantiations v
mapInstantiations u -> v
f GenInstantiations u
is))
homeUnitMap u -> v
f (IndefiniteHomeUnit UnitId
u GenInstantiations u
is) = UnitId -> GenInstantiations v -> GenHomeUnit v
forall u. UnitId -> GenInstantiations u -> GenHomeUnit u
IndefiniteHomeUnit UnitId
u ((u -> v) -> GenInstantiations u -> GenInstantiations v
forall v u.
IsUnitId v =>
(u -> v) -> GenInstantiations u -> GenInstantiations v
mapInstantiations u -> v
f GenInstantiations u
is)
isHomeUnitIndefinite :: GenHomeUnit u -> Bool
isHomeUnitIndefinite :: forall u. GenHomeUnit u -> Bool
isHomeUnitIndefinite (DefiniteHomeUnit {}) = Bool
False
isHomeUnitIndefinite (IndefiniteHomeUnit {}) = Bool
True
isHomeUnitDefinite :: GenHomeUnit u -> Bool
isHomeUnitDefinite :: forall u. GenHomeUnit u -> Bool
isHomeUnitDefinite (DefiniteHomeUnit {}) = Bool
True
isHomeUnitDefinite (IndefiniteHomeUnit {}) = Bool
False
isHomeUnitInstantiating :: GenHomeUnit u -> Bool
isHomeUnitInstantiating :: forall u. GenHomeUnit u -> Bool
isHomeUnitInstantiating GenHomeUnit u
u =
GenHomeUnit u -> Bool
forall u. GenHomeUnit u -> Bool
isHomeUnitDefinite GenHomeUnit u
u Bool -> Bool -> Bool
&& Bool -> Bool
not ([(ModuleName, GenModule (GenUnit u))] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (GenHomeUnit u -> [(ModuleName, GenModule (GenUnit u))]
forall u. GenHomeUnit u -> GenInstantiations u
homeUnitInstantiations GenHomeUnit u
u))
isHomeUnit :: HomeUnit -> Unit -> Bool
isHomeUnit :: HomeUnit -> Unit -> Bool
isHomeUnit HomeUnit
hu Unit
u = Unit
u Unit -> Unit -> Bool
forall a. Eq a => a -> a -> Bool
== HomeUnit -> Unit
homeUnitAsUnit HomeUnit
hu
isHomeUnitId :: GenHomeUnit u -> UnitId -> Bool
isHomeUnitId :: forall u. GenHomeUnit u -> UnitId -> Bool
isHomeUnitId GenHomeUnit u
hu UnitId
uid = UnitId
uid UnitId -> UnitId -> Bool
forall a. Eq a => a -> a -> Bool
== GenHomeUnit u -> UnitId
forall u. GenHomeUnit u -> UnitId
homeUnitId GenHomeUnit u
hu
isHomeUnitInstanceOf :: HomeUnit -> UnitId -> Bool
isHomeUnitInstanceOf :: HomeUnit -> UnitId -> Bool
isHomeUnitInstanceOf HomeUnit
hu UnitId
u = HomeUnit -> UnitId
homeUnitInstanceOf HomeUnit
hu UnitId -> UnitId -> Bool
forall a. Eq a => a -> a -> Bool
== UnitId
u
isHomeModule :: HomeUnit -> Module -> Bool
isHomeModule :: HomeUnit -> Module -> Bool
isHomeModule HomeUnit
hu Module
m = HomeUnit -> Unit -> Bool
isHomeUnit HomeUnit
hu (Module -> Unit
forall unit. GenModule unit -> unit
moduleUnit Module
m)
isHomeInstalledModule :: GenHomeUnit u -> InstalledModule -> Bool
isHomeInstalledModule :: forall u. GenHomeUnit u -> InstalledModule -> Bool
isHomeInstalledModule GenHomeUnit u
hu InstalledModule
m = GenHomeUnit u -> UnitId -> Bool
forall u. GenHomeUnit u -> UnitId -> Bool
isHomeUnitId GenHomeUnit u
hu (InstalledModule -> UnitId
forall unit. GenModule unit -> unit
moduleUnit InstalledModule
m)
notHomeInstalledModule :: GenHomeUnit u -> InstalledModule -> Bool
notHomeInstalledModule :: forall u. GenHomeUnit u -> InstalledModule -> Bool
notHomeInstalledModule GenHomeUnit u
hu InstalledModule
m = Bool -> Bool
not (GenHomeUnit u -> InstalledModule -> Bool
forall u. GenHomeUnit u -> InstalledModule -> Bool
isHomeInstalledModule GenHomeUnit u
hu InstalledModule
m)
notHomeInstalledModuleMaybe :: Maybe (GenHomeUnit u) -> InstalledModule -> Bool
notHomeInstalledModuleMaybe :: forall u. Maybe (GenHomeUnit u) -> InstalledModule -> Bool
notHomeInstalledModuleMaybe Maybe (GenHomeUnit u)
mh InstalledModule
m = Bool -> Maybe Bool -> Bool
forall a. a -> Maybe a -> a
fromMaybe Bool
True (Maybe Bool -> Bool) -> Maybe Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (GenHomeUnit u -> Bool) -> Maybe (GenHomeUnit u) -> Maybe Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (GenHomeUnit u -> InstalledModule -> Bool
forall u. GenHomeUnit u -> InstalledModule -> Bool
`notHomeInstalledModule` InstalledModule
m) Maybe (GenHomeUnit u)
mh
notHomeModule :: HomeUnit -> Module -> Bool
notHomeModule :: HomeUnit -> Module -> Bool
notHomeModule HomeUnit
hu Module
m = Bool -> Bool
not (HomeUnit -> Module -> Bool
isHomeModule HomeUnit
hu Module
m)
notHomeModuleMaybe :: Maybe HomeUnit -> Module -> Bool
notHomeModuleMaybe :: Maybe HomeUnit -> Module -> Bool
notHomeModuleMaybe Maybe HomeUnit
mh Module
m = Bool -> Maybe Bool -> Bool
forall a. a -> Maybe a -> a
fromMaybe Bool
True (Maybe Bool -> Bool) -> Maybe Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (HomeUnit -> Bool) -> Maybe HomeUnit -> Maybe Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (HomeUnit -> Module -> Bool
`notHomeModule` Module
m) Maybe HomeUnit
mh
mkHomeModule :: HomeUnit -> ModuleName -> Module
mkHomeModule :: HomeUnit -> ModuleName -> Module
mkHomeModule HomeUnit
hu = Unit -> ModuleName -> Module
forall u. u -> ModuleName -> GenModule u
mkModule (HomeUnit -> Unit
homeUnitAsUnit HomeUnit
hu)
mkHomeInstalledModule :: GenHomeUnit u -> ModuleName -> InstalledModule
mkHomeInstalledModule :: forall u. GenHomeUnit u -> ModuleName -> InstalledModule
mkHomeInstalledModule GenHomeUnit u
hu = UnitId -> ModuleName -> InstalledModule
forall u. u -> ModuleName -> GenModule u
mkModule (GenHomeUnit u -> UnitId
forall u. GenHomeUnit u -> UnitId
homeUnitId GenHomeUnit u
hu)
homeModuleNameInstantiation :: HomeUnit -> ModuleName -> Module
homeModuleNameInstantiation :: HomeUnit -> ModuleName -> Module
homeModuleNameInstantiation HomeUnit
hu ModuleName
mod_name =
case ModuleName -> GenInstantiations UnitId -> Maybe Module
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup ModuleName
mod_name (HomeUnit -> GenInstantiations UnitId
forall u. GenHomeUnit u -> GenInstantiations u
homeUnitInstantiations HomeUnit
hu) of
Maybe Module
Nothing -> HomeUnit -> ModuleName -> Module
mkHomeModule HomeUnit
hu ModuleName
mod_name
Just Module
mod -> Module
mod
homeModuleInstantiation :: HomeUnit -> Module -> Module
homeModuleInstantiation :: HomeUnit -> Module -> Module
homeModuleInstantiation HomeUnit
hu Module
mod
| HomeUnit -> Module -> Bool
isHomeModule HomeUnit
hu Module
mod = HomeUnit -> ModuleName -> Module
homeModuleNameInstantiation HomeUnit
hu (Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
mod)
| Bool
otherwise = Module
mod