module GHC.Unit.Env
    ( UnitEnv (..)
    , preloadUnitsInfo
    , preloadUnitsInfo'
    )
where

import GHC.Prelude

import GHC.Unit.State
import GHC.Unit.Home
import GHC.Unit.Types

import GHC.Platform
import GHC.Settings
import GHC.Data.Maybe

data UnitEnv = UnitEnv
    { UnitEnv -> UnitState
ue_units     :: !UnitState      -- ^ Units
    , UnitEnv -> HomeUnit
ue_home_unit :: !HomeUnit       -- ^ Home unit
    , UnitEnv -> Platform
ue_platform  :: !Platform       -- ^ Platform
    , UnitEnv -> GhcNameVersion
ue_namever   :: !GhcNameVersion -- ^ GHC name/version (used for dynamic library suffix)
    }

-- -----------------------------------------------------------------------------
-- Extracting information from the packages in scope

-- Many of these functions take a list of packages: in those cases,
-- the list is expected to contain the "dependent packages",
-- i.e. those packages that were found to be depended on by the
-- current module/program.  These can be auto or non-auto packages, it
-- doesn't really matter.  The list is always combined with the list
-- of preload (command-line) packages to determine which packages to
-- use.

-- | Lookup 'UnitInfo' for every preload unit from the UnitState, for every unit
-- used to instantiate the home unit, and for every unit explicitly passed in
-- the given list of UnitId.
preloadUnitsInfo' :: UnitEnv -> [UnitId] -> MaybeErr UnitErr [UnitInfo]
preloadUnitsInfo' :: UnitEnv -> [UnitId] -> MaybeErr UnitErr [UnitInfo]
preloadUnitsInfo' UnitEnv
unit_env [UnitId]
ids0 = MaybeErr UnitErr [UnitInfo]
all_infos
  where
    home_unit :: HomeUnit
home_unit  = UnitEnv -> HomeUnit
ue_home_unit UnitEnv
unit_env
    unit_state :: UnitState
unit_state = UnitEnv -> UnitState
ue_units     UnitEnv
unit_env
    ids :: [UnitId]
ids      = [UnitId]
ids0 forall a. [a] -> [a] -> [a]
++ [UnitId]
inst_ids
    inst_ids :: [UnitId]
inst_ids
       -- An indefinite package will have insts to HOLE,
       -- which is not a real package. Don't look it up.
       -- Fixes #14525
       | forall u. GenHomeUnit u -> Bool
isHomeUnitIndefinite HomeUnit
home_unit = []
       | Bool
otherwise = forall a b. (a -> b) -> [a] -> [b]
map (Unit -> UnitId
toUnitId forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall unit. GenModule unit -> unit
moduleUnit forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd) (forall u. GenHomeUnit u -> GenInstantiations u
homeUnitInstantiations HomeUnit
home_unit)
    pkg_map :: UnitInfoMap
pkg_map = UnitState -> UnitInfoMap
unitInfoMap UnitState
unit_state
    preload :: [UnitId]
preload = UnitState -> [UnitId]
preloadUnits UnitState
unit_state

    all_pkgs :: MaybeErr UnitErr [UnitId]
all_pkgs  = UnitInfoMap
-> [UnitId]
-> [(UnitId, Maybe UnitId)]
-> MaybeErr UnitErr [UnitId]
closeUnitDeps' UnitInfoMap
pkg_map [UnitId]
preload ([UnitId]
ids forall a b. [a] -> [b] -> [(a, b)]
`zip` forall a. a -> [a]
repeat forall a. Maybe a
Nothing)
    all_infos :: MaybeErr UnitErr [UnitInfo]
all_infos = forall a b. (a -> b) -> [a] -> [b]
map (HasDebugCallStack => UnitState -> UnitId -> UnitInfo
unsafeLookupUnitId UnitState
unit_state) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MaybeErr UnitErr [UnitId]
all_pkgs


-- | Lookup 'UnitInfo' for every preload unit from the UnitState and for every
-- unit used to instantiate the home unit.
preloadUnitsInfo :: UnitEnv -> MaybeErr UnitErr [UnitInfo]
preloadUnitsInfo :: UnitEnv -> MaybeErr UnitErr [UnitInfo]
preloadUnitsInfo UnitEnv
unit_env = UnitEnv -> [UnitId] -> MaybeErr UnitErr [UnitInfo]
preloadUnitsInfo' UnitEnv
unit_env []