-- (c) The University of Glasgow, 2006

{-# LANGUAGE CPP, ScopedTypeVariables, BangPatterns, FlexibleContexts #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE LambdaCase #-}

-- | Unit manipulation
module GHC.Unit.State (
        module GHC.Unit.Info,

        -- * Reading the package config, and processing cmdline args
        UnitState(..),
        PreloadUnitClosure,
        UnitDatabase (..),
        UnitErr (..),
        emptyUnitState,
        initUnits,
        readUnitDatabases,
        readUnitDatabase,
        getUnitDbRefs,
        resolveUnitDatabase,
        listUnitInfo,

        -- * Querying the package config
        UnitInfoMap,
        lookupUnit,
        lookupUnit',
        unsafeLookupUnit,
        lookupUnitId,
        lookupUnitId',
        unsafeLookupUnitId,

        lookupPackageName,
        improveUnit,
        searchPackageId,
        listVisibleModuleNames,
        lookupModuleInAllUnits,
        lookupModuleWithSuggestions,
        lookupModulePackage,
        lookupPluginModuleWithSuggestions,
        requirementMerges,
        LookupResult(..),
        ModuleSuggestion(..),
        ModuleOrigin(..),
        UnusableUnitReason(..),
        pprReason,

        closeUnitDeps,
        closeUnitDeps',
        mayThrowUnitErr,

        -- * Module hole substitution
        ShHoleSubst,
        renameHoleUnit,
        renameHoleModule,
        renameHoleUnit',
        renameHoleModule',
        instUnitToUnit,
        instModuleToModule,

        -- * Pretty-printing
        pprFlag,
        pprUnits,
        pprUnitsSimple,
        pprUnitIdForUser,
        pprUnitInfoForUser,
        pprModuleMap,
        pprWithUnitState,

        -- * Utils
        unwireUnit
    )
where

#include "HsVersions.h"

import GHC.Prelude

import GHC.Driver.Session

import GHC.Platform
import GHC.Platform.Ways

import GHC.Unit.Database
import GHC.Unit.Info
import GHC.Unit.Ppr
import GHC.Unit.Types
import GHC.Unit.Module
import GHC.Unit.Home

import GHC.Types.Unique.FM
import GHC.Types.Unique.DFM
import GHC.Types.Unique.Set
import GHC.Types.Unique.DSet

import GHC.Utils.Misc
import GHC.Utils.Panic
import GHC.Utils.Outputable as Outputable
import GHC.Data.Maybe

import System.Environment ( getEnv )
import GHC.Data.FastString
import qualified GHC.Data.ShortText as ST
import GHC.Utils.Logger
import GHC.Utils.Error
import GHC.Utils.Exception

import System.Directory
import System.FilePath as FilePath
import Control.Monad
import Data.Graph (stronglyConnComp, SCC(..))
import Data.Char ( toUpper )
import Data.List ( intersperse, partition, sortBy, isSuffixOf )
import Data.Map (Map)
import Data.Set (Set)
import Data.Monoid (First(..))
import qualified Data.Semigroup as Semigroup
import qualified Data.Map as Map
import qualified Data.Map.Strict as MapStrict
import qualified Data.Set as Set

-- ---------------------------------------------------------------------------
-- The Unit state

-- The unit state is computed by 'initUnits', and kept in HscEnv.
-- It is influenced by various command-line flags:
--
--   * @-package \<pkg>@ and @-package-id \<pkg>@ cause @\<pkg>@ to become exposed.
--     If @-hide-all-packages@ was not specified, these commands also cause
--      all other packages with the same name to become hidden.
--
--   * @-hide-package \<pkg>@ causes @\<pkg>@ to become hidden.
--
--   * (there are a few more flags, check below for their semantics)
--
-- The unit state has the following properties.
--
--   * Let @exposedUnits@ be the set of packages thus exposed.
--     Let @depExposedUnits@ be the transitive closure from @exposedUnits@ of
--     their dependencies.
--
--   * When searching for a module from a preload import declaration,
--     only the exposed modules in @exposedUnits@ are valid.
--
--   * When searching for a module from an implicit import, all modules
--     from @depExposedUnits@ are valid.
--
--   * When linking in a compilation manager mode, we link in packages the
--     program depends on (the compiler knows this list by the
--     time it gets to the link step).  Also, we link in all packages
--     which were mentioned with preload @-package@ flags on the command-line,
--     or are a transitive dependency of same, or are \"base\"\/\"rts\".
--     The reason for this is that we might need packages which don't
--     contain any Haskell modules, and therefore won't be discovered
--     by the normal mechanism of dependency tracking.

-- Notes on DLLs
-- ~~~~~~~~~~~~~
-- When compiling module A, which imports module B, we need to
-- know whether B will be in the same DLL as A.
--      If it's in the same DLL, we refer to B_f_closure
--      If it isn't, we refer to _imp__B_f_closure
-- When compiling A, we record in B's Module value whether it's
-- in a different DLL, by setting the DLL flag.

-- | Given a module name, there may be multiple ways it came into scope,
-- possibly simultaneously.  This data type tracks all the possible ways
-- it could have come into scope.  Warning: don't use the record functions,
-- they're partial!
data ModuleOrigin =
    -- | Module is hidden, and thus never will be available for import.
    -- (But maybe the user didn't realize), so we'll still keep track
    -- of these modules.)
    ModHidden
    -- | Module is unavailable because the package is unusable.
  | ModUnusable UnusableUnitReason
    -- | Module is public, and could have come from some places.
  | ModOrigin {
        -- | @Just False@ means that this module is in
        -- someone's @exported-modules@ list, but that package is hidden;
        -- @Just True@ means that it is available; @Nothing@ means neither
        -- applies.
        ModuleOrigin -> Maybe Bool
fromOrigUnit :: Maybe Bool
        -- | Is the module available from a reexport of an exposed package?
        -- There could be multiple.
      , ModuleOrigin -> [UnitInfo]
fromExposedReexport :: [UnitInfo]
        -- | Is the module available from a reexport of a hidden package?
      , ModuleOrigin -> [UnitInfo]
fromHiddenReexport :: [UnitInfo]
        -- | Did the module export come from a package flag? (ToDo: track
        -- more information.
      , ModuleOrigin -> Bool
fromPackageFlag :: Bool
      }

instance Outputable ModuleOrigin where
    ppr :: ModuleOrigin -> SDoc
ppr ModuleOrigin
ModHidden = String -> SDoc
text String
"hidden module"
    ppr (ModUnusable UnusableUnitReason
_) = String -> SDoc
text String
"unusable module"
    ppr (ModOrigin Maybe Bool
e [UnitInfo]
res [UnitInfo]
rhs Bool
f) = [SDoc] -> SDoc
sep (SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
comma (
        (case Maybe Bool
e of
            Maybe Bool
Nothing -> []
            Just Bool
False -> [String -> SDoc
text String
"hidden package"]
            Just Bool
True -> [String -> SDoc
text String
"exposed package"]) forall a. [a] -> [a] -> [a]
++
        (if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [UnitInfo]
res
            then []
            else [String -> SDoc
text String
"reexport by" SDoc -> SDoc -> SDoc
<+>
                    [SDoc] -> SDoc
sep (forall a b. (a -> b) -> [a] -> [b]
map (forall a. Outputable a => a -> SDoc
ppr forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnitInfo -> GenUnit UnitId
mkUnit) [UnitInfo]
res)]) forall a. [a] -> [a] -> [a]
++
        (if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [UnitInfo]
rhs
            then []
            else [String -> SDoc
text String
"hidden reexport by" SDoc -> SDoc -> SDoc
<+>
                    [SDoc] -> SDoc
sep (forall a b. (a -> b) -> [a] -> [b]
map (forall a. Outputable a => a -> SDoc
ppr forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnitInfo -> GenUnit UnitId
mkUnit) [UnitInfo]
res)]) forall a. [a] -> [a] -> [a]
++
        (if Bool
f then [String -> SDoc
text String
"package flag"] else [])
        ))

-- | Smart constructor for a module which is in @exposed-modules@.  Takes
-- as an argument whether or not the defining package is exposed.
fromExposedModules :: Bool -> ModuleOrigin
fromExposedModules :: Bool -> ModuleOrigin
fromExposedModules Bool
e = Maybe Bool -> [UnitInfo] -> [UnitInfo] -> Bool -> ModuleOrigin
ModOrigin (forall a. a -> Maybe a
Just Bool
e) [] [] Bool
False

-- | Smart constructor for a module which is in @reexported-modules@.  Takes
-- as an argument whether or not the reexporting package is exposed, and
-- also its 'UnitInfo'.
fromReexportedModules :: Bool -> UnitInfo -> ModuleOrigin
fromReexportedModules :: Bool -> UnitInfo -> ModuleOrigin
fromReexportedModules Bool
True UnitInfo
pkg = Maybe Bool -> [UnitInfo] -> [UnitInfo] -> Bool -> ModuleOrigin
ModOrigin forall a. Maybe a
Nothing [UnitInfo
pkg] [] Bool
False
fromReexportedModules Bool
False UnitInfo
pkg = Maybe Bool -> [UnitInfo] -> [UnitInfo] -> Bool -> ModuleOrigin
ModOrigin forall a. Maybe a
Nothing [] [UnitInfo
pkg] Bool
False

-- | Smart constructor for a module which was bound by a package flag.
fromFlag :: ModuleOrigin
fromFlag :: ModuleOrigin
fromFlag = Maybe Bool -> [UnitInfo] -> [UnitInfo] -> Bool -> ModuleOrigin
ModOrigin forall a. Maybe a
Nothing [] [] Bool
True

instance Semigroup ModuleOrigin where
    x :: ModuleOrigin
x@(ModOrigin Maybe Bool
e [UnitInfo]
res [UnitInfo]
rhs Bool
f) <> :: ModuleOrigin -> ModuleOrigin -> ModuleOrigin
<> y :: ModuleOrigin
y@(ModOrigin Maybe Bool
e' [UnitInfo]
res' [UnitInfo]
rhs' Bool
f') =
        Maybe Bool -> [UnitInfo] -> [UnitInfo] -> Bool -> ModuleOrigin
ModOrigin (Maybe Bool -> Maybe Bool -> Maybe Bool
g Maybe Bool
e Maybe Bool
e') ([UnitInfo]
res forall a. [a] -> [a] -> [a]
++ [UnitInfo]
res') ([UnitInfo]
rhs forall a. [a] -> [a] -> [a]
++ [UnitInfo]
rhs') (Bool
f Bool -> Bool -> Bool
|| Bool
f')
      where g :: Maybe Bool -> Maybe Bool -> Maybe Bool
g (Just Bool
b) (Just Bool
b')
                | Bool
b forall a. Eq a => a -> a -> Bool
== Bool
b'   = forall a. a -> Maybe a
Just Bool
b
                | Bool
otherwise = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"ModOrigin: package both exposed/hidden" forall a b. (a -> b) -> a -> b
$
                    String -> SDoc
text String
"x: " SDoc -> SDoc -> SDoc
<> forall a. Outputable a => a -> SDoc
ppr ModuleOrigin
x SDoc -> SDoc -> SDoc
$$ String -> SDoc
text String
"y: " SDoc -> SDoc -> SDoc
<> forall a. Outputable a => a -> SDoc
ppr ModuleOrigin
y
            g Maybe Bool
Nothing Maybe Bool
x = Maybe Bool
x
            g Maybe Bool
x Maybe Bool
Nothing = Maybe Bool
x
    ModuleOrigin
x <> ModuleOrigin
y = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"ModOrigin: hidden module redefined" forall a b. (a -> b) -> a -> b
$
                 String -> SDoc
text String
"x: " SDoc -> SDoc -> SDoc
<> forall a. Outputable a => a -> SDoc
ppr ModuleOrigin
x SDoc -> SDoc -> SDoc
$$ String -> SDoc
text String
"y: " SDoc -> SDoc -> SDoc
<> forall a. Outputable a => a -> SDoc
ppr ModuleOrigin
y

instance Monoid ModuleOrigin where
    mempty :: ModuleOrigin
mempty = Maybe Bool -> [UnitInfo] -> [UnitInfo] -> Bool -> ModuleOrigin
ModOrigin forall a. Maybe a
Nothing [] [] Bool
False
    mappend :: ModuleOrigin -> ModuleOrigin -> ModuleOrigin
mappend = forall a. Semigroup a => a -> a -> a
(Semigroup.<>)

-- | Is the name from the import actually visible? (i.e. does it cause
-- ambiguity, or is it only relevant when we're making suggestions?)
originVisible :: ModuleOrigin -> Bool
originVisible :: ModuleOrigin -> Bool
originVisible ModuleOrigin
ModHidden = Bool
False
originVisible (ModUnusable UnusableUnitReason
_) = Bool
False
originVisible (ModOrigin Maybe Bool
b [UnitInfo]
res [UnitInfo]
_ Bool
f) = Maybe Bool
b forall a. Eq a => a -> a -> Bool
== forall a. a -> Maybe a
Just Bool
True Bool -> Bool -> Bool
|| Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [UnitInfo]
res) Bool -> Bool -> Bool
|| Bool
f

-- | Are there actually no providers for this module?  This will never occur
-- except when we're filtering based on package imports.
originEmpty :: ModuleOrigin -> Bool
originEmpty :: ModuleOrigin -> Bool
originEmpty (ModOrigin Maybe Bool
Nothing [] [] Bool
False) = Bool
True
originEmpty ModuleOrigin
_ = Bool
False

type PreloadUnitClosure = UniqSet UnitId

-- | 'UniqFM' map from 'Unit' to a 'UnitVisibility'.
type VisibilityMap = Map Unit UnitVisibility

-- | 'UnitVisibility' records the various aspects of visibility of a particular
-- 'Unit'.
data UnitVisibility = UnitVisibility
    { UnitVisibility -> Bool
uv_expose_all :: Bool
      --  ^ Should all modules in exposed-modules should be dumped into scope?
    , UnitVisibility -> [(ModuleName, ModuleName)]
uv_renamings :: [(ModuleName, ModuleName)]
      -- ^ Any custom renamings that should bring extra 'ModuleName's into
      -- scope.
    , UnitVisibility -> First FastString
uv_package_name :: First FastString
      -- ^ The package name associated with the 'Unit'.  This is used
      -- to implement legacy behavior where @-package foo-0.1@ implicitly
      -- hides any packages named @foo@
    , UnitVisibility -> Map ModuleName (Set InstantiatedModule)
uv_requirements :: Map ModuleName (Set InstantiatedModule)
      -- ^ The signatures which are contributed to the requirements context
      -- from this unit ID.
    , UnitVisibility -> Bool
uv_explicit :: Bool
      -- ^ Whether or not this unit was explicitly brought into scope,
      -- as opposed to implicitly via the 'exposed' fields in the
      -- package database (when @-hide-all-packages@ is not passed.)
    }

instance Outputable UnitVisibility where
    ppr :: UnitVisibility -> SDoc
ppr (UnitVisibility {
        uv_expose_all :: UnitVisibility -> Bool
uv_expose_all = Bool
b,
        uv_renamings :: UnitVisibility -> [(ModuleName, ModuleName)]
uv_renamings = [(ModuleName, ModuleName)]
rns,
        uv_package_name :: UnitVisibility -> First FastString
uv_package_name = First Maybe FastString
mb_pn,
        uv_requirements :: UnitVisibility -> Map ModuleName (Set InstantiatedModule)
uv_requirements = Map ModuleName (Set InstantiatedModule)
reqs,
        uv_explicit :: UnitVisibility -> Bool
uv_explicit = Bool
explicit
    }) = forall a. Outputable a => a -> SDoc
ppr (Bool
b, [(ModuleName, ModuleName)]
rns, Maybe FastString
mb_pn, Map ModuleName (Set InstantiatedModule)
reqs, Bool
explicit)

instance Semigroup UnitVisibility where
    UnitVisibility
uv1 <> :: UnitVisibility -> UnitVisibility -> UnitVisibility
<> UnitVisibility
uv2
        = UnitVisibility
          { uv_expose_all :: Bool
uv_expose_all = UnitVisibility -> Bool
uv_expose_all UnitVisibility
uv1 Bool -> Bool -> Bool
|| UnitVisibility -> Bool
uv_expose_all UnitVisibility
uv2
          , uv_renamings :: [(ModuleName, ModuleName)]
uv_renamings = UnitVisibility -> [(ModuleName, ModuleName)]
uv_renamings UnitVisibility
uv1 forall a. [a] -> [a] -> [a]
++ UnitVisibility -> [(ModuleName, ModuleName)]
uv_renamings UnitVisibility
uv2
          , uv_package_name :: First FastString
uv_package_name = forall a. Monoid a => a -> a -> a
mappend (UnitVisibility -> First FastString
uv_package_name UnitVisibility
uv1) (UnitVisibility -> First FastString
uv_package_name UnitVisibility
uv2)
          , uv_requirements :: Map ModuleName (Set InstantiatedModule)
uv_requirements = forall k a. Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
Map.unionWith forall a. Ord a => Set a -> Set a -> Set a
Set.union (UnitVisibility -> Map ModuleName (Set InstantiatedModule)
uv_requirements UnitVisibility
uv1) (UnitVisibility -> Map ModuleName (Set InstantiatedModule)
uv_requirements UnitVisibility
uv2)
          , uv_explicit :: Bool
uv_explicit = UnitVisibility -> Bool
uv_explicit UnitVisibility
uv1 Bool -> Bool -> Bool
|| UnitVisibility -> Bool
uv_explicit UnitVisibility
uv2
          }

instance Monoid UnitVisibility where
    mempty :: UnitVisibility
mempty = UnitVisibility
             { uv_expose_all :: Bool
uv_expose_all = Bool
False
             , uv_renamings :: [(ModuleName, ModuleName)]
uv_renamings = []
             , uv_package_name :: First FastString
uv_package_name = forall a. Maybe a -> First a
First forall a. Maybe a
Nothing
             , uv_requirements :: Map ModuleName (Set InstantiatedModule)
uv_requirements = forall k a. Map k a
Map.empty
             , uv_explicit :: Bool
uv_explicit = Bool
False
             }
    mappend :: UnitVisibility -> UnitVisibility -> UnitVisibility
mappend = forall a. Semigroup a => a -> a -> a
(Semigroup.<>)


-- | Unit configuration
data UnitConfig = UnitConfig
   { UnitConfig -> ArchOS
unitConfigPlatformArchOS :: !ArchOS        -- ^ Platform arch and OS
   , UnitConfig -> Ways
unitConfigWays           :: !Ways          -- ^ Ways to use

   , UnitConfig -> Bool
unitConfigAllowVirtual   :: !Bool          -- ^ Allow virtual units
      -- ^ Do we allow the use of virtual units instantiated on-the-fly (see Note
      -- [About units] in GHC.Unit). This should only be true when we are
      -- type-checking an indefinite unit (not producing any code).

   , UnitConfig -> String
unitConfigProgramName    :: !String
      -- ^ Name of the compiler (e.g. "GHC", "GHCJS"). Used to fetch environment
      -- variables such as "GHC[JS]_PACKAGE_PATH".

   , UnitConfig -> String
unitConfigGlobalDB :: !FilePath    -- ^ Path to global DB
   , UnitConfig -> String
unitConfigGHCDir   :: !FilePath    -- ^ Main GHC dir: contains settings, etc.
   , UnitConfig -> String
unitConfigDBName   :: !String      -- ^ User DB name (e.g. "package.conf.d")

   , UnitConfig -> [UnitId]
unitConfigAutoLink       :: ![UnitId] -- ^ Units to link automatically (e.g. base, rts)
   , UnitConfig -> Bool
unitConfigDistrustAll    :: !Bool     -- ^ Distrust all units by default
   , UnitConfig -> Bool
unitConfigHideAll        :: !Bool     -- ^ Hide all units by default
   , UnitConfig -> Bool
unitConfigHideAllPlugins :: !Bool     -- ^ Hide all plugins units by default

   , UnitConfig -> Maybe [UnitDatabase UnitId]
unitConfigDBCache      :: Maybe [UnitDatabase UnitId]
      -- ^ Cache of databases to use, in the order they were specified on the
      -- command line (later databases shadow earlier ones).
      -- If Nothing, databases will be found using `unitConfigFlagsDB`.

   -- command-line flags
   , UnitConfig -> [PackageDBFlag]
unitConfigFlagsDB      :: [PackageDBFlag]     -- ^ Unit databases flags
   , UnitConfig -> [PackageFlag]
unitConfigFlagsExposed :: [PackageFlag]       -- ^ Exposed units
   , UnitConfig -> [IgnorePackageFlag]
unitConfigFlagsIgnored :: [IgnorePackageFlag] -- ^ Ignored units
   , UnitConfig -> [TrustFlag]
unitConfigFlagsTrusted :: [TrustFlag]         -- ^ Trusted units
   , UnitConfig -> [PackageFlag]
unitConfigFlagsPlugins :: [PackageFlag]       -- ^ Plugins exposed units
   }

initUnitConfig :: DynFlags -> Maybe [UnitDatabase UnitId] -> UnitConfig
initUnitConfig :: DynFlags -> Maybe [UnitDatabase UnitId] -> UnitConfig
initUnitConfig DynFlags
dflags Maybe [UnitDatabase UnitId]
cached_dbs =
   let !hu_id :: UnitId
hu_id             = DynFlags -> UnitId
homeUnitId_ DynFlags
dflags
       !hu_instanceof :: Maybe UnitId
hu_instanceof     = DynFlags -> Maybe UnitId
homeUnitInstanceOf_ DynFlags
dflags
       !hu_instantiations :: [(ModuleName, Module)]
hu_instantiations = DynFlags -> [(ModuleName, Module)]
homeUnitInstantiations_ DynFlags
dflags

       autoLink :: [UnitId]
autoLink
         | Bool -> Bool
not (GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_AutoLinkPackages DynFlags
dflags) = []
         -- By default we add base & rts to the preload units (when they are
         -- found in the unit database) except when we are building them
         | Bool
otherwise = forall a. (a -> Bool) -> [a] -> [a]
filter (UnitId
hu_id forall a. Eq a => a -> a -> Bool
/=) [UnitId
baseUnitId, UnitId
rtsUnitId]

       -- if the home unit is indefinite, it means we are type-checking it only
       -- (not producing any code). Hence we can use virtual units instantiated
       -- on-the-fly. See Note [About units] in GHC.Unit
       allow_virtual_units :: Bool
allow_virtual_units = case (Maybe UnitId
hu_instanceof, [(ModuleName, Module)]
hu_instantiations) of
            (Just UnitId
u, [(ModuleName, Module)]
is) -> UnitId
u forall a. Eq a => a -> a -> Bool
== UnitId
hu_id Bool -> Bool -> Bool
&& forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall u. GenModule (GenUnit u) -> Bool
isHoleModule forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd) [(ModuleName, Module)]
is
            (Maybe UnitId, [(ModuleName, Module)])
_            -> Bool
False

   in UnitConfig
      { unitConfigPlatformArchOS :: ArchOS
unitConfigPlatformArchOS = Platform -> ArchOS
platformArchOS (DynFlags -> Platform
targetPlatform DynFlags
dflags)
      , unitConfigProgramName :: String
unitConfigProgramName    = DynFlags -> String
programName DynFlags
dflags
      , unitConfigWays :: Ways
unitConfigWays           = DynFlags -> Ways
ways DynFlags
dflags
      , unitConfigAllowVirtual :: Bool
unitConfigAllowVirtual   = Bool
allow_virtual_units

      , unitConfigGlobalDB :: String
unitConfigGlobalDB       = DynFlags -> String
globalPackageDatabasePath DynFlags
dflags
      , unitConfigGHCDir :: String
unitConfigGHCDir         = DynFlags -> String
topDir DynFlags
dflags
      , unitConfigDBName :: String
unitConfigDBName         = String
"package.conf.d"

      , unitConfigAutoLink :: [UnitId]
unitConfigAutoLink       = [UnitId]
autoLink
      , unitConfigDistrustAll :: Bool
unitConfigDistrustAll    = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_DistrustAllPackages DynFlags
dflags
      , unitConfigHideAll :: Bool
unitConfigHideAll        = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_HideAllPackages DynFlags
dflags
      , unitConfigHideAllPlugins :: Bool
unitConfigHideAllPlugins = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_HideAllPluginPackages DynFlags
dflags

      , unitConfigDBCache :: Maybe [UnitDatabase UnitId]
unitConfigDBCache      = Maybe [UnitDatabase UnitId]
cached_dbs
      , unitConfigFlagsDB :: [PackageDBFlag]
unitConfigFlagsDB      = DynFlags -> [PackageDBFlag]
packageDBFlags DynFlags
dflags
      , unitConfigFlagsExposed :: [PackageFlag]
unitConfigFlagsExposed = DynFlags -> [PackageFlag]
packageFlags DynFlags
dflags
      , unitConfigFlagsIgnored :: [IgnorePackageFlag]
unitConfigFlagsIgnored = DynFlags -> [IgnorePackageFlag]
ignorePackageFlags DynFlags
dflags
      , unitConfigFlagsTrusted :: [TrustFlag]
unitConfigFlagsTrusted = DynFlags -> [TrustFlag]
trustFlags DynFlags
dflags
      , unitConfigFlagsPlugins :: [PackageFlag]
unitConfigFlagsPlugins = DynFlags -> [PackageFlag]
pluginPackageFlags DynFlags
dflags

      }

-- | Map from 'ModuleName' to a set of module providers (i.e. a 'Module' and
-- its 'ModuleOrigin').
--
-- NB: the set is in fact a 'Map Module ModuleOrigin', probably to keep only one
-- origin for a given 'Module'
type ModuleNameProvidersMap =
    Map ModuleName (Map Module ModuleOrigin)

data UnitState = UnitState {
  -- | A mapping of 'Unit' to 'UnitInfo'.  This list is adjusted
  -- so that only valid units are here.  'UnitInfo' reflects
  -- what was stored *on disk*, except for the 'trusted' flag, which
  -- is adjusted at runtime.  (In particular, some units in this map
  -- may have the 'exposed' flag be 'False'.)
  UnitState -> UnitInfoMap
unitInfoMap :: UnitInfoMap,

  -- | The set of transitively reachable units according
  -- to the explicitly provided command line arguments.
  -- A fully instantiated VirtUnit may only be replaced by a RealUnit from
  -- this set.
  -- See Note [VirtUnit to RealUnit improvement]
  UnitState -> PreloadUnitClosure
preloadClosure :: PreloadUnitClosure,

  -- | A mapping of 'PackageName' to 'IndefUnitId'.  This is used when
  -- users refer to packages in Backpack includes.
  UnitState -> UniqFM PackageName IndefUnitId
packageNameMap            :: UniqFM PackageName IndefUnitId,

  -- | A mapping from database unit keys to wired in unit ids.
  UnitState -> Map UnitId UnitId
wireMap :: Map UnitId UnitId,

  -- | A mapping from wired in unit ids to unit keys from the database.
  UnitState -> Map UnitId UnitId
unwireMap :: Map UnitId UnitId,

  -- | The units we're going to link in eagerly.  This list
  -- should be in reverse dependency order; that is, a unit
  -- is always mentioned before the units it depends on.
  UnitState -> [UnitId]
preloadUnits      :: [UnitId],

  -- | Units which we explicitly depend on (from a command line flag).
  -- We'll use this to generate version macros.
  UnitState -> [GenUnit UnitId]
explicitUnits      :: [Unit],

  -- | This is a full map from 'ModuleName' to all modules which may possibly
  -- be providing it.  These providers may be hidden (but we'll still want
  -- to report them in error messages), or it may be an ambiguous import.
  UnitState -> ModuleNameProvidersMap
moduleNameProvidersMap    :: !ModuleNameProvidersMap,

  -- | A map, like 'moduleNameProvidersMap', but controlling plugin visibility.
  UnitState -> ModuleNameProvidersMap
pluginModuleNameProvidersMap    :: !ModuleNameProvidersMap,

  -- | A map saying, for each requirement, what interfaces must be merged
  -- together when we use them.  For example, if our dependencies
  -- are @p[A=\<A>]@ and @q[A=\<A>,B=r[C=\<A>]:B]@, then the interfaces
  -- to merge for A are @p[A=\<A>]:A@, @q[A=\<A>,B=r[C=\<A>]:B]:A@
  -- and @r[C=\<A>]:C@.
  --
  -- There's an entry in this map for each hole in our home library.
  UnitState -> Map ModuleName [InstantiatedModule]
requirementContext :: Map ModuleName [InstantiatedModule],

  -- | Indicate if we can instantiate units on-the-fly.
  --
  -- This should only be true when we are type-checking an indefinite unit.
  -- See Note [About units] in GHC.Unit.
  UnitState -> Bool
allowVirtualUnits :: !Bool
  }

emptyUnitState :: UnitState
emptyUnitState :: UnitState
emptyUnitState = UnitState {
    unitInfoMap :: UnitInfoMap
unitInfoMap = forall k a. Map k a
Map.empty,
    preloadClosure :: PreloadUnitClosure
preloadClosure = forall a. UniqSet a
emptyUniqSet,
    packageNameMap :: UniqFM PackageName IndefUnitId
packageNameMap = forall key elt. UniqFM key elt
emptyUFM,
    wireMap :: Map UnitId UnitId
wireMap   = forall k a. Map k a
Map.empty,
    unwireMap :: Map UnitId UnitId
unwireMap = forall k a. Map k a
Map.empty,
    preloadUnits :: [UnitId]
preloadUnits = [],
    explicitUnits :: [GenUnit UnitId]
explicitUnits = [],
    moduleNameProvidersMap :: ModuleNameProvidersMap
moduleNameProvidersMap = forall k a. Map k a
Map.empty,
    pluginModuleNameProvidersMap :: ModuleNameProvidersMap
pluginModuleNameProvidersMap = forall k a. Map k a
Map.empty,
    requirementContext :: Map ModuleName [InstantiatedModule]
requirementContext = forall k a. Map k a
Map.empty,
    allowVirtualUnits :: Bool
allowVirtualUnits = Bool
False
    }

-- | Unit database
data UnitDatabase unit = UnitDatabase
   { forall unit. UnitDatabase unit -> String
unitDatabasePath  :: FilePath
   , forall unit. UnitDatabase unit -> [GenUnitInfo unit]
unitDatabaseUnits :: [GenUnitInfo unit]
   }

type UnitInfoMap = Map UnitId UnitInfo

-- | Find the unit we know about with the given unit, if any
lookupUnit :: UnitState -> Unit -> Maybe UnitInfo
lookupUnit :: UnitState -> GenUnit UnitId -> Maybe UnitInfo
lookupUnit UnitState
pkgs = Bool
-> UnitInfoMap
-> PreloadUnitClosure
-> GenUnit UnitId
-> Maybe UnitInfo
lookupUnit' (UnitState -> Bool
allowVirtualUnits UnitState
pkgs) (UnitState -> UnitInfoMap
unitInfoMap UnitState
pkgs) (UnitState -> PreloadUnitClosure
preloadClosure UnitState
pkgs)

-- | A more specialized interface, which doesn't require a 'UnitState' (so it
-- can be used while we're initializing 'DynFlags')
--
-- Parameters:
--    * a boolean specifying whether or not to look for on-the-fly renamed interfaces
--    * a 'UnitInfoMap'
--    * a 'PreloadUnitClosure'
lookupUnit' :: Bool -> UnitInfoMap -> PreloadUnitClosure -> Unit -> Maybe UnitInfo
lookupUnit' :: Bool
-> UnitInfoMap
-> PreloadUnitClosure
-> GenUnit UnitId
-> Maybe UnitInfo
lookupUnit' Bool
allowOnTheFlyInst UnitInfoMap
pkg_map PreloadUnitClosure
closure GenUnit UnitId
u = case GenUnit UnitId
u of
   GenUnit UnitId
HoleUnit   -> forall a. HasCallStack => String -> a
error String
"Hole unit"
   RealUnit Definite UnitId
i -> forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (forall unit. Definite unit -> unit
unDefinite Definite UnitId
i) UnitInfoMap
pkg_map
   VirtUnit GenInstantiatedUnit UnitId
i
      | Bool
allowOnTheFlyInst
      -> -- lookup UnitInfo of the indefinite unit to be instantiated and
         -- instantiate it on-the-fly
         forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (UnitInfoMap
-> PreloadUnitClosure
-> [(ModuleName, Module)]
-> UnitInfo
-> UnitInfo
renameUnitInfo UnitInfoMap
pkg_map PreloadUnitClosure
closure (forall unit. GenInstantiatedUnit unit -> GenInstantiations unit
instUnitInsts GenInstantiatedUnit UnitId
i))
           (forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (forall unit. Indefinite unit -> unit
indefUnit (forall unit. GenInstantiatedUnit unit -> Indefinite unit
instUnitInstanceOf GenInstantiatedUnit UnitId
i)) UnitInfoMap
pkg_map)

      | Bool
otherwise
      -> -- lookup UnitInfo by virtual UnitId. This is used to find indefinite
         -- units. Even if they are real, installed units, they can't use the
         -- `RealUnit` constructor (it is reserved for definite units) so we use
         -- the `VirtUnit` constructor.
         forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (GenInstantiatedUnit UnitId -> UnitId
virtualUnitId GenInstantiatedUnit UnitId
i) UnitInfoMap
pkg_map

-- | Find the unit we know about with the given unit id, if any
lookupUnitId :: UnitState -> UnitId -> Maybe UnitInfo
lookupUnitId :: UnitState -> UnitId -> Maybe UnitInfo
lookupUnitId UnitState
state UnitId
uid = UnitInfoMap -> UnitId -> Maybe UnitInfo
lookupUnitId' (UnitState -> UnitInfoMap
unitInfoMap UnitState
state) UnitId
uid

-- | Find the unit we know about with the given unit id, if any
lookupUnitId' :: UnitInfoMap -> UnitId -> Maybe UnitInfo
lookupUnitId' :: UnitInfoMap -> UnitId -> Maybe UnitInfo
lookupUnitId' UnitInfoMap
db UnitId
uid = forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UnitId
uid UnitInfoMap
db


-- | Looks up the given unit in the unit state, panicing if it is not found
unsafeLookupUnit :: HasDebugCallStack => UnitState -> Unit -> UnitInfo
unsafeLookupUnit :: HasDebugCallStack => UnitState -> GenUnit UnitId -> UnitInfo
unsafeLookupUnit UnitState
state GenUnit UnitId
u = case UnitState -> GenUnit UnitId -> Maybe UnitInfo
lookupUnit UnitState
state GenUnit UnitId
u of
   Just UnitInfo
info -> UnitInfo
info
   Maybe UnitInfo
Nothing   -> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"unsafeLookupUnit" (forall a. Outputable a => a -> SDoc
ppr GenUnit UnitId
u)

-- | Looks up the given unit id in the unit state, panicing if it is not found
unsafeLookupUnitId :: HasDebugCallStack => UnitState -> UnitId -> UnitInfo
unsafeLookupUnitId :: HasDebugCallStack => UnitState -> UnitId -> UnitInfo
unsafeLookupUnitId UnitState
state UnitId
uid = case UnitState -> UnitId -> Maybe UnitInfo
lookupUnitId UnitState
state UnitId
uid of
   Just UnitInfo
info -> UnitInfo
info
   Maybe UnitInfo
Nothing   -> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"unsafeLookupUnitId" (forall a. Outputable a => a -> SDoc
ppr UnitId
uid)


-- | Find the unit we know about with the given package name (e.g. @foo@), if any
-- (NB: there might be a locally defined unit name which overrides this)
lookupPackageName :: UnitState -> PackageName -> Maybe IndefUnitId
lookupPackageName :: UnitState -> PackageName -> Maybe IndefUnitId
lookupPackageName UnitState
pkgstate PackageName
n = forall key elt. Uniquable key => UniqFM key elt -> key -> Maybe elt
lookupUFM (UnitState -> UniqFM PackageName IndefUnitId
packageNameMap UnitState
pkgstate) PackageName
n

-- | Search for units with a given package ID (e.g. \"foo-0.1\")
searchPackageId :: UnitState -> PackageId -> [UnitInfo]
searchPackageId :: UnitState -> PackageId -> [UnitInfo]
searchPackageId UnitState
pkgstate PackageId
pid = forall a. (a -> Bool) -> [a] -> [a]
filter ((PackageId
pid forall a. Eq a => a -> a -> Bool
==) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> srcpkgid
unitPackageId)
                               (UnitState -> [UnitInfo]
listUnitInfo UnitState
pkgstate)

-- | Create a Map UnitId UnitInfo
--
-- For each instantiated unit, we add two map keys:
--    * the real unit id
--    * the virtual unit id made from its instantiation
--
-- We do the same thing for fully indefinite units (which are "instantiated"
-- with module holes).
--
mkUnitInfoMap :: [UnitInfo] -> UnitInfoMap
mkUnitInfoMap :: [UnitInfo] -> UnitInfoMap
mkUnitInfoMap [UnitInfo]
infos = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' forall {srcpkgid} {srcpkgname}.
Map
  UnitId
  (GenericUnitInfo
     IndefUnitId srcpkgid srcpkgname UnitId ModuleName Module)
-> GenericUnitInfo
     IndefUnitId srcpkgid srcpkgname UnitId ModuleName Module
-> Map
     UnitId
     (GenericUnitInfo
        IndefUnitId srcpkgid srcpkgname UnitId ModuleName Module)
add forall k a. Map k a
Map.empty [UnitInfo]
infos
  where
   mkVirt :: GenericUnitInfo
  IndefUnitId srcpkgid srcpkgname uid ModuleName Module
-> UnitId
mkVirt      GenericUnitInfo
  IndefUnitId srcpkgid srcpkgname uid ModuleName Module
p = GenInstantiatedUnit UnitId -> UnitId
virtualUnitId (forall u.
IsUnitId u =>
Indefinite u -> GenInstantiations u -> GenInstantiatedUnit u
mkInstantiatedUnit (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> compid
unitInstanceOf GenericUnitInfo
  IndefUnitId srcpkgid srcpkgname uid ModuleName Module
p) (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [(modulename, mod)]
unitInstantiations GenericUnitInfo
  IndefUnitId srcpkgid srcpkgname uid ModuleName Module
p))
   add :: Map
  UnitId
  (GenericUnitInfo
     IndefUnitId srcpkgid srcpkgname UnitId ModuleName Module)
-> GenericUnitInfo
     IndefUnitId srcpkgid srcpkgname UnitId ModuleName Module
-> Map
     UnitId
     (GenericUnitInfo
        IndefUnitId srcpkgid srcpkgname UnitId ModuleName Module)
add Map
  UnitId
  (GenericUnitInfo
     IndefUnitId srcpkgid srcpkgname UnitId ModuleName Module)
pkg_map GenericUnitInfo
  IndefUnitId srcpkgid srcpkgname UnitId ModuleName Module
p
      | Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [(modulename, mod)]
unitInstantiations GenericUnitInfo
  IndefUnitId srcpkgid srcpkgname UnitId ModuleName Module
p))
      = forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (forall {srcpkgid} {srcpkgname} {uid}.
GenericUnitInfo
  IndefUnitId srcpkgid srcpkgname uid ModuleName Module
-> UnitId
mkVirt GenericUnitInfo
  IndefUnitId srcpkgid srcpkgname UnitId ModuleName Module
p) GenericUnitInfo
  IndefUnitId srcpkgid srcpkgname UnitId ModuleName Module
p
         forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId GenericUnitInfo
  IndefUnitId srcpkgid srcpkgname UnitId ModuleName Module
p) GenericUnitInfo
  IndefUnitId srcpkgid srcpkgname UnitId ModuleName Module
p
         forall a b. (a -> b) -> a -> b
$ Map
  UnitId
  (GenericUnitInfo
     IndefUnitId srcpkgid srcpkgname UnitId ModuleName Module)
pkg_map
      | Bool
otherwise
      = forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId GenericUnitInfo
  IndefUnitId srcpkgid srcpkgname UnitId ModuleName Module
p) GenericUnitInfo
  IndefUnitId srcpkgid srcpkgname UnitId ModuleName Module
p Map
  UnitId
  (GenericUnitInfo
     IndefUnitId srcpkgid srcpkgname UnitId ModuleName Module)
pkg_map

-- | Get a list of entries from the unit database.  NB: be careful with
-- this function, although all units in this map are "visible", this
-- does not imply that the exposed-modules of the unit are available
-- (they may have been thinned or renamed).
listUnitInfo :: UnitState -> [UnitInfo]
listUnitInfo :: UnitState -> [UnitInfo]
listUnitInfo UnitState
state = forall k a. Map k a -> [a]
Map.elems (UnitState -> UnitInfoMap
unitInfoMap UnitState
state)

-- ----------------------------------------------------------------------------
-- Loading the unit db files and building up the unit state

-- | Read the unit database files, and sets up various internal tables of
-- unit information, according to the unit-related flags on the
-- command-line (@-package@, @-hide-package@ etc.)
--
-- 'initUnits' can be called again subsequently after updating the
-- 'packageFlags' field of the 'DynFlags', and it will update the
-- 'unitState' in 'DynFlags'.
initUnits :: Logger -> DynFlags -> Maybe [UnitDatabase UnitId] -> IO ([UnitDatabase UnitId], UnitState, HomeUnit, Maybe PlatformConstants)
initUnits :: Logger
-> DynFlags
-> Maybe [UnitDatabase UnitId]
-> IO
     ([UnitDatabase UnitId], UnitState, HomeUnit,
      Maybe PlatformConstants)
initUnits Logger
logger DynFlags
dflags Maybe [UnitDatabase UnitId]
cached_dbs = do

  let forceUnitInfoMap :: (UnitState, b) -> ()
forceUnitInfoMap (UnitState
state, b
_) = UnitState -> UnitInfoMap
unitInfoMap UnitState
state seq :: forall a b. a -> b -> b
`seq` ()
  let ctx :: SDocContext
ctx     = DynFlags -> PprStyle -> SDocContext
initSDocContext DynFlags
dflags PprStyle
defaultUserStyle -- SDocContext used to render exception messages
  let printer :: Int -> SDoc -> IO ()
printer = Logger -> DynFlags -> Int -> SDoc -> IO ()
debugTraceMsg Logger
logger DynFlags
dflags             -- printer for trace messages

  (UnitState
unit_state,[UnitDatabase UnitId]
dbs) <- forall (m :: * -> *) a.
MonadIO m =>
Logger -> DynFlags -> SDoc -> (a -> ()) -> m a -> m a
withTiming Logger
logger DynFlags
dflags (String -> SDoc
text String
"initializing unit database")
                   forall {b}. (UnitState, b) -> ()
forceUnitInfoMap
                 forall a b. (a -> b) -> a -> b
$ SDocContext
-> (Int -> SDoc -> IO ())
-> UnitConfig
-> IO (UnitState, [UnitDatabase UnitId])
mkUnitState SDocContext
ctx Int -> SDoc -> IO ()
printer (DynFlags -> Maybe [UnitDatabase UnitId] -> UnitConfig
initUnitConfig DynFlags
dflags Maybe [UnitDatabase UnitId]
cached_dbs)

  Logger
-> DynFlags -> DumpFlag -> String -> DumpFormat -> SDoc -> IO ()
dumpIfSet_dyn Logger
logger DynFlags
dflags DumpFlag
Opt_D_dump_mod_map String
"Module Map"
    DumpFormat
FormatText ((SDocContext -> SDocContext) -> SDoc -> SDoc
updSDocContext (\SDocContext
ctx -> SDocContext
ctx {sdocLineLength :: Int
sdocLineLength = Int
200})
                forall a b. (a -> b) -> a -> b
$ ModuleNameProvidersMap -> SDoc
pprModuleMap (UnitState -> ModuleNameProvidersMap
moduleNameProvidersMap UnitState
unit_state))

  let home_unit :: HomeUnit
home_unit = UnitState
-> UnitId -> Maybe UnitId -> [(ModuleName, Module)] -> HomeUnit
mkHomeUnit UnitState
unit_state
                             (DynFlags -> UnitId
homeUnitId_ DynFlags
dflags)
                             (DynFlags -> Maybe UnitId
homeUnitInstanceOf_ DynFlags
dflags)
                             (DynFlags -> [(ModuleName, Module)]
homeUnitInstantiations_ DynFlags
dflags)

  -- Try to find platform constants
  --
  -- See Note [Platform constants] in GHC.Platform
  Maybe PlatformConstants
mconstants <- if DynFlags -> UnitId
homeUnitId_ DynFlags
dflags forall a. Eq a => a -> a -> Bool
== UnitId
rtsUnitId
    then do
      -- we're building the RTS! Lookup DerivedConstants.h in the include paths
      [String] -> IO (Maybe PlatformConstants)
lookupPlatformConstants (IncludeSpecs -> [String]
includePathsGlobal (DynFlags -> IncludeSpecs
includePaths DynFlags
dflags))
    else
      -- lookup the DerivedConstants.h header bundled with the RTS unit. We
      -- don't fail if we can't find the RTS unit as it can be a valid (but
      -- uncommon) case, e.g. building a C utility program (not depending on the
      -- RTS) before building the RTS. In any case, we will fail later on if we
      -- really need to use the platform constants but they have not been loaded.
      case UnitState -> UnitId -> Maybe UnitInfo
lookupUnitId UnitState
unit_state UnitId
rtsUnitId of
        Maybe UnitInfo
Nothing   -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
        Just UnitInfo
info -> [String] -> IO (Maybe PlatformConstants)
lookupPlatformConstants (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShortText -> String
ST.unpack (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitIncludeDirs UnitInfo
info))

  forall (m :: * -> *) a. Monad m => a -> m a
return ([UnitDatabase UnitId]
dbs,UnitState
unit_state,HomeUnit
home_unit,Maybe PlatformConstants
mconstants)

mkHomeUnit
    :: UnitState
    -> UnitId                 -- ^ Home unit id
    -> Maybe UnitId           -- ^ Home unit instance of
    -> [(ModuleName, Module)] -- ^ Home unit instantiations
    -> HomeUnit
mkHomeUnit :: UnitState
-> UnitId -> Maybe UnitId -> [(ModuleName, Module)] -> HomeUnit
mkHomeUnit UnitState
unit_state UnitId
hu_id Maybe UnitId
hu_instanceof [(ModuleName, Module)]
hu_instantiations_ =
    let
        -- Some wired units can be used to instantiate the home unit. We need to
        -- replace their unit keys with their wired unit ids.
        wmap :: Map UnitId UnitId
wmap              = UnitState -> Map UnitId UnitId
wireMap UnitState
unit_state
        hu_instantiations :: [(ModuleName, Module)]
hu_instantiations = forall a b. (a -> b) -> [a] -> [b]
map (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Map UnitId UnitId -> Module -> Module
upd_wired_in_mod Map UnitId UnitId
wmap)) [(ModuleName, Module)]
hu_instantiations_
    in case (Maybe UnitId
hu_instanceof, [(ModuleName, Module)]
hu_instantiations) of
      (Maybe UnitId
Nothing,[]) -> forall u. UnitId -> Maybe (u, GenInstantiations u) -> GenHomeUnit u
DefiniteHomeUnit UnitId
hu_id forall a. Maybe a
Nothing
      (Maybe UnitId
Nothing, [(ModuleName, Module)]
_) -> forall a. GhcException -> a
throwGhcException forall a b. (a -> b) -> a -> b
$ String -> GhcException
CmdLineError (String
"Use of -instantiated-with requires -this-component-id")
      (Just UnitId
_, []) -> forall a. GhcException -> a
throwGhcException forall a b. (a -> b) -> a -> b
$ String -> GhcException
CmdLineError (String
"Use of -this-component-id requires -instantiated-with")
      (Just UnitId
u, [(ModuleName, Module)]
is)
         -- detect fully indefinite units: all their instantiations are hole
         -- modules and the home unit id is the same as the instantiating unit
         -- id (see Note [About units] in GHC.Unit)
         | forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (forall u. GenModule (GenUnit u) -> Bool
isHoleModule forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd) [(ModuleName, Module)]
is Bool -> Bool -> Bool
&& UnitId
u forall a. Eq a => a -> a -> Bool
== UnitId
hu_id
         -> forall u. UnitId -> GenInstantiations u -> GenHomeUnit u
IndefiniteHomeUnit UnitId
u [(ModuleName, Module)]
is
         -- otherwise it must be that we (fully) instantiate an indefinite unit
         -- to make it definite.
         -- TODO: error when the unit is partially instantiated??
         | Bool
otherwise
         -> forall u. UnitId -> Maybe (u, GenInstantiations u) -> GenHomeUnit u
DefiniteHomeUnit UnitId
hu_id (forall a. a -> Maybe a
Just (UnitId
u, [(ModuleName, Module)]
is))

-- -----------------------------------------------------------------------------
-- Reading the unit database(s)

readUnitDatabases :: (Int -> SDoc -> IO ()) -> UnitConfig -> IO [UnitDatabase UnitId]
readUnitDatabases :: (Int -> SDoc -> IO ()) -> UnitConfig -> IO [UnitDatabase UnitId]
readUnitDatabases Int -> SDoc -> IO ()
printer UnitConfig
cfg = do
  [PkgDbRef]
conf_refs <- UnitConfig -> IO [PkgDbRef]
getUnitDbRefs UnitConfig
cfg
  [String]
confs     <- forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM forall a. [Maybe a] -> [a]
catMaybes forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (UnitConfig -> PkgDbRef -> IO (Maybe String)
resolveUnitDatabase UnitConfig
cfg) [PkgDbRef]
conf_refs
  forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((Int -> SDoc -> IO ())
-> UnitConfig -> String -> IO (UnitDatabase UnitId)
readUnitDatabase Int -> SDoc -> IO ()
printer UnitConfig
cfg) [String]
confs


getUnitDbRefs :: UnitConfig -> IO [PkgDbRef]
getUnitDbRefs :: UnitConfig -> IO [PkgDbRef]
getUnitDbRefs UnitConfig
cfg = do
  let system_conf_refs :: [PkgDbRef]
system_conf_refs = [PkgDbRef
UserPkgDb, PkgDbRef
GlobalPkgDb]

  Either IOException String
e_pkg_path <- forall a. IO a -> IO (Either IOException a)
tryIO (String -> IO String
getEnv forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toUpper (UnitConfig -> String
unitConfigProgramName UnitConfig
cfg) forall a. [a] -> [a] -> [a]
++ String
"_PACKAGE_PATH")
  let base_conf_refs :: [PkgDbRef]
base_conf_refs = case Either IOException String
e_pkg_path of
        Left IOException
_ -> [PkgDbRef]
system_conf_refs
        Right String
path
         | Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
path) Bool -> Bool -> Bool
&& Char -> Bool
isSearchPathSeparator (forall a. [a] -> a
last String
path)
         -> forall a b. (a -> b) -> [a] -> [b]
map String -> PkgDbRef
PkgDbPath (String -> [String]
splitSearchPath (forall a. [a] -> [a]
init String
path)) forall a. [a] -> [a] -> [a]
++ [PkgDbRef]
system_conf_refs
         | Bool
otherwise
         -> forall a b. (a -> b) -> [a] -> [b]
map String -> PkgDbRef
PkgDbPath (String -> [String]
splitSearchPath String
path)

  -- Apply the package DB-related flags from the command line to get the
  -- final list of package DBs.
  --
  -- Notes on ordering:
  --  * The list of flags is reversed (later ones first)
  --  * We work with the package DB list in "left shadows right" order
  --  * and finally reverse it at the end, to get "right shadows left"
  --
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
reverse (forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr PackageDBFlag -> [PkgDbRef] -> [PkgDbRef]
doFlag [PkgDbRef]
base_conf_refs (UnitConfig -> [PackageDBFlag]
unitConfigFlagsDB UnitConfig
cfg))
 where
  doFlag :: PackageDBFlag -> [PkgDbRef] -> [PkgDbRef]
doFlag (PackageDB PkgDbRef
p) [PkgDbRef]
dbs = PkgDbRef
p forall a. a -> [a] -> [a]
: [PkgDbRef]
dbs
  doFlag PackageDBFlag
NoUserPackageDB [PkgDbRef]
dbs = forall a. (a -> Bool) -> [a] -> [a]
filter PkgDbRef -> Bool
isNotUser [PkgDbRef]
dbs
  doFlag PackageDBFlag
NoGlobalPackageDB [PkgDbRef]
dbs = forall a. (a -> Bool) -> [a] -> [a]
filter PkgDbRef -> Bool
isNotGlobal [PkgDbRef]
dbs
  doFlag PackageDBFlag
ClearPackageDBs [PkgDbRef]
_ = []

  isNotUser :: PkgDbRef -> Bool
isNotUser PkgDbRef
UserPkgDb = Bool
False
  isNotUser PkgDbRef
_ = Bool
True

  isNotGlobal :: PkgDbRef -> Bool
isNotGlobal PkgDbRef
GlobalPkgDb = Bool
False
  isNotGlobal PkgDbRef
_ = Bool
True

-- | Return the path of a package database from a 'PkgDbRef'. Return 'Nothing'
-- when the user database filepath is expected but the latter doesn't exist.
--
-- NB: This logic is reimplemented in Cabal, so if you change it,
-- make sure you update Cabal. (Or, better yet, dump it in the
-- compiler info so Cabal can use the info.)
resolveUnitDatabase :: UnitConfig -> PkgDbRef -> IO (Maybe FilePath)
resolveUnitDatabase :: UnitConfig -> PkgDbRef -> IO (Maybe String)
resolveUnitDatabase UnitConfig
cfg PkgDbRef
GlobalPkgDb = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just (UnitConfig -> String
unitConfigGlobalDB UnitConfig
cfg)
resolveUnitDatabase UnitConfig
cfg PkgDbRef
UserPkgDb = forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT forall a b. (a -> b) -> a -> b
$ do
  String
dir <- String -> ArchOS -> MaybeT IO String
versionedAppDir (UnitConfig -> String
unitConfigProgramName UnitConfig
cfg) (UnitConfig -> ArchOS
unitConfigPlatformArchOS UnitConfig
cfg)
  let pkgconf :: String
pkgconf = String
dir String -> String -> String
</> UnitConfig -> String
unitConfigDBName UnitConfig
cfg
  Bool
exist <- forall a. IO a -> MaybeT IO a
tryMaybeT forall a b. (a -> b) -> a -> b
$ String -> IO Bool
doesDirectoryExist String
pkgconf
  if Bool
exist then forall (m :: * -> *) a. Monad m => a -> m a
return String
pkgconf else forall (m :: * -> *) a. MonadPlus m => m a
mzero
resolveUnitDatabase UnitConfig
_ (PkgDbPath String
name) = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just String
name

readUnitDatabase :: (Int -> SDoc -> IO ()) -> UnitConfig -> FilePath -> IO (UnitDatabase UnitId)
readUnitDatabase :: (Int -> SDoc -> IO ())
-> UnitConfig -> String -> IO (UnitDatabase UnitId)
readUnitDatabase Int -> SDoc -> IO ()
printer UnitConfig
cfg String
conf_file = do
  Bool
isdir <- String -> IO Bool
doesDirectoryExist String
conf_file

  [DbUnitInfo]
proto_pkg_configs <-
    if Bool
isdir
       then String -> IO [DbUnitInfo]
readDirStyleUnitInfo String
conf_file
       else do
            Bool
isfile <- String -> IO Bool
doesFileExist String
conf_file
            if Bool
isfile
               then do
                 Maybe [DbUnitInfo]
mpkgs <- IO (Maybe [DbUnitInfo])
tryReadOldFileStyleUnitInfo
                 case Maybe [DbUnitInfo]
mpkgs of
                   Just [DbUnitInfo]
pkgs -> forall (m :: * -> *) a. Monad m => a -> m a
return [DbUnitInfo]
pkgs
                   Maybe [DbUnitInfo]
Nothing   -> forall a. GhcException -> IO a
throwGhcExceptionIO forall a b. (a -> b) -> a -> b
$ String -> GhcException
InstallationError forall a b. (a -> b) -> a -> b
$
                      String
"ghc no longer supports single-file style package " forall a. [a] -> [a] -> [a]
++
                      String
"databases (" forall a. [a] -> [a] -> [a]
++ String
conf_file forall a. [a] -> [a] -> [a]
++
                      String
") use 'ghc-pkg init' to create the database with " forall a. [a] -> [a] -> [a]
++
                      String
"the correct format."
               else forall a. GhcException -> IO a
throwGhcExceptionIO forall a b. (a -> b) -> a -> b
$ String -> GhcException
InstallationError forall a b. (a -> b) -> a -> b
$
                      String
"can't find a package database at " forall a. [a] -> [a] -> [a]
++ String
conf_file

  let
      -- Fix #16360: remove trailing slash from conf_file before calculating pkgroot
      conf_file' :: String
conf_file' = String -> String
dropTrailingPathSeparator String
conf_file
      top_dir :: String
top_dir = UnitConfig -> String
unitConfigGHCDir UnitConfig
cfg
      pkgroot :: String
pkgroot = String -> String
takeDirectory String
conf_file'
      pkg_configs1 :: [UnitInfo]
pkg_configs1 = forall a b. (a -> b) -> [a] -> [b]
map (String -> String -> UnitInfo -> UnitInfo
mungeUnitInfo String
top_dir String
pkgroot forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall v u.
IsUnitId v =>
(u -> v) -> GenUnitInfo u -> GenUnitInfo v
mapUnitInfo (\(UnitKey FastString
x) -> FastString -> UnitId
UnitId FastString
x) forall b c a. (b -> c) -> (a -> b) -> a -> c
. DbUnitInfo -> UnitKeyInfo
mkUnitKeyInfo)
                         [DbUnitInfo]
proto_pkg_configs
  --
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall unit. String -> [GenUnitInfo unit] -> UnitDatabase unit
UnitDatabase String
conf_file' [UnitInfo]
pkg_configs1
  where
    readDirStyleUnitInfo :: String -> IO [DbUnitInfo]
readDirStyleUnitInfo String
conf_dir = do
      let filename :: String
filename = String
conf_dir String -> String -> String
</> String
"package.cache"
      Bool
cache_exists <- String -> IO Bool
doesFileExist String
filename
      if Bool
cache_exists
        then do
          Int -> SDoc -> IO ()
printer Int
2 forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"Using binary package database:" SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
filename
          String -> IO [DbUnitInfo]
readPackageDbForGhc String
filename
        else do
          -- If there is no package.cache file, we check if the database is not
          -- empty by inspecting if the directory contains any .conf file. If it
          -- does, something is wrong and we fail. Otherwise we assume that the
          -- database is empty.
          Int -> SDoc -> IO ()
printer Int
2 forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"There is no package.cache in"
                      SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
conf_dir
                       SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
", checking if the database is empty"
          Bool
db_empty <- forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Eq a => [a] -> [a] -> Bool
isSuffixOf String
".conf")
                   forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO [String]
getDirectoryContents String
conf_dir
          if Bool
db_empty
            then do
              Int -> SDoc -> IO ()
printer Int
3 forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"There are no .conf files in"
                          SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
conf_dir SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
", treating"
                          SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"package database as empty"
              forall (m :: * -> *) a. Monad m => a -> m a
return []
            else
              forall a. GhcException -> IO a
throwGhcExceptionIO forall a b. (a -> b) -> a -> b
$ String -> GhcException
InstallationError forall a b. (a -> b) -> a -> b
$
                String
"there is no package.cache in " forall a. [a] -> [a] -> [a]
++ String
conf_dir forall a. [a] -> [a] -> [a]
++
                String
" even though package database is not empty"


    -- Single-file style package dbs have been deprecated for some time, but
    -- it turns out that Cabal was using them in one place. So this is a
    -- workaround to allow older Cabal versions to use this newer ghc.
    -- We check if the file db contains just "[]" and if so, we look for a new
    -- dir-style db in conf_file.d/, ie in a dir next to the given file.
    -- We cannot just replace the file with a new dir style since Cabal still
    -- assumes it's a file and tries to overwrite with 'writeFile'.
    -- ghc-pkg also cooperates with this workaround.
    tryReadOldFileStyleUnitInfo :: IO (Maybe [DbUnitInfo])
tryReadOldFileStyleUnitInfo = do
      String
content <- String -> IO String
readFile String
conf_file forall a. IO a -> (IOException -> IO a) -> IO a
`catchIO` \IOException
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return String
""
      if forall a. Int -> [a] -> [a]
take Int
2 String
content forall a. Eq a => a -> a -> Bool
== String
"[]"
        then do
          let conf_dir :: String
conf_dir = String
conf_file String -> String -> String
<.> String
"d"
          Bool
direxists <- String -> IO Bool
doesDirectoryExist String
conf_dir
          if Bool
direxists
             then do Int -> SDoc -> IO ()
printer Int
2 (String -> SDoc
text String
"Ignoring old file-style db and trying:" SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
conf_dir)
                     forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM forall a. a -> Maybe a
Just (String -> IO [DbUnitInfo]
readDirStyleUnitInfo String
conf_dir)
             else forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just []) -- ghc-pkg will create it when it's updated
        else forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing

distrustAllUnits :: [UnitInfo] -> [UnitInfo]
distrustAllUnits :: [UnitInfo] -> [UnitInfo]
distrustAllUnits [UnitInfo]
pkgs = forall a b. (a -> b) -> [a] -> [b]
map forall {compid} {srcpkgid} {srcpkgname} {uid} {modulename} {mod}.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
distrust [UnitInfo]
pkgs
  where
    distrust :: GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
distrust GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
pkg = GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
pkg{ unitIsTrusted :: Bool
unitIsTrusted = Bool
False }

mungeUnitInfo :: FilePath -> FilePath
                   -> UnitInfo -> UnitInfo
mungeUnitInfo :: String -> String -> UnitInfo -> UnitInfo
mungeUnitInfo String
top_dir String
pkgroot =
    UnitInfo -> UnitInfo
mungeDynLibFields
  forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c d e f.
ShortText
-> ShortText
-> GenericUnitInfo a b c d e f
-> GenericUnitInfo a b c d e f
mungeUnitInfoPaths (String -> ShortText
ST.pack String
top_dir) (String -> ShortText
ST.pack String
pkgroot)

mungeDynLibFields :: UnitInfo -> UnitInfo
mungeDynLibFields :: UnitInfo -> UnitInfo
mungeDynLibFields UnitInfo
pkg =
    UnitInfo
pkg {
      unitLibraryDynDirs :: [ShortText]
unitLibraryDynDirs = case forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitLibraryDynDirs UnitInfo
pkg of
         [] -> forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [ShortText]
unitLibraryDirs UnitInfo
pkg
         [ShortText]
ds -> [ShortText]
ds
    }

-- -----------------------------------------------------------------------------
-- Modify our copy of the unit database based on trust flags,
-- -trust and -distrust.

applyTrustFlag
   :: UnitPrecedenceMap
   -> UnusableUnits
   -> [UnitInfo]
   -> TrustFlag
   -> MaybeErr UnitErr [UnitInfo]
applyTrustFlag :: UnitPrecedenceMap
-> UnusableUnits
-> [UnitInfo]
-> TrustFlag
-> MaybeErr UnitErr [UnitInfo]
applyTrustFlag UnitPrecedenceMap
prec_map UnusableUnits
unusable [UnitInfo]
pkgs TrustFlag
flag =
  case TrustFlag
flag of
    -- we trust all matching packages. Maybe should only trust first one?
    -- and leave others the same or set them untrusted
    TrustPackage String
str ->
       case UnitPrecedenceMap
-> PackageArg
-> [UnitInfo]
-> UnusableUnits
-> Either [(UnitInfo, UnusableUnitReason)] ([UnitInfo], [UnitInfo])
selectPackages UnitPrecedenceMap
prec_map (String -> PackageArg
PackageArg String
str) [UnitInfo]
pkgs UnusableUnits
unusable of
         Left [(UnitInfo, UnusableUnitReason)]
ps       -> forall err val. err -> MaybeErr err val
Failed (TrustFlag -> [(UnitInfo, UnusableUnitReason)] -> UnitErr
TrustFlagErr TrustFlag
flag [(UnitInfo, UnusableUnitReason)]
ps)
         Right ([UnitInfo]
ps,[UnitInfo]
qs) -> forall err val. val -> MaybeErr err val
Succeeded (forall a b. (a -> b) -> [a] -> [b]
map forall {compid} {srcpkgid} {srcpkgname} {uid} {modulename} {mod}.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
trust [UnitInfo]
ps forall a. [a] -> [a] -> [a]
++ [UnitInfo]
qs)
          where trust :: GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
trust GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
p = GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
p {unitIsTrusted :: Bool
unitIsTrusted=Bool
True}

    DistrustPackage String
str ->
       case UnitPrecedenceMap
-> PackageArg
-> [UnitInfo]
-> UnusableUnits
-> Either [(UnitInfo, UnusableUnitReason)] ([UnitInfo], [UnitInfo])
selectPackages UnitPrecedenceMap
prec_map (String -> PackageArg
PackageArg String
str) [UnitInfo]
pkgs UnusableUnits
unusable of
         Left [(UnitInfo, UnusableUnitReason)]
ps       -> forall err val. err -> MaybeErr err val
Failed (TrustFlag -> [(UnitInfo, UnusableUnitReason)] -> UnitErr
TrustFlagErr TrustFlag
flag [(UnitInfo, UnusableUnitReason)]
ps)
         Right ([UnitInfo]
ps,[UnitInfo]
qs) -> forall err val. val -> MaybeErr err val
Succeeded ([UnitInfo] -> [UnitInfo]
distrustAllUnits [UnitInfo]
ps forall a. [a] -> [a] -> [a]
++ [UnitInfo]
qs)

applyPackageFlag
   :: UnitPrecedenceMap
   -> UnitInfoMap
   -> PreloadUnitClosure
   -> UnusableUnits
   -> Bool -- if False, if you expose a package, it implicitly hides
           -- any previously exposed packages with the same name
   -> [UnitInfo]
   -> VisibilityMap           -- Initially exposed
   -> PackageFlag             -- flag to apply
   -> MaybeErr UnitErr VisibilityMap -- Now exposed

applyPackageFlag :: UnitPrecedenceMap
-> UnitInfoMap
-> PreloadUnitClosure
-> UnusableUnits
-> Bool
-> [UnitInfo]
-> VisibilityMap
-> PackageFlag
-> MaybeErr UnitErr VisibilityMap
applyPackageFlag UnitPrecedenceMap
prec_map UnitInfoMap
pkg_map PreloadUnitClosure
closure UnusableUnits
unusable Bool
no_hide_others [UnitInfo]
pkgs VisibilityMap
vm PackageFlag
flag =
  case PackageFlag
flag of
    ExposePackage String
_ PackageArg
arg (ModRenaming Bool
b [(ModuleName, ModuleName)]
rns) ->
       case UnitPrecedenceMap
-> UnitInfoMap
-> PreloadUnitClosure
-> PackageArg
-> [UnitInfo]
-> UnusableUnits
-> Either [(UnitInfo, UnusableUnitReason)] [UnitInfo]
findPackages UnitPrecedenceMap
prec_map UnitInfoMap
pkg_map PreloadUnitClosure
closure PackageArg
arg [UnitInfo]
pkgs UnusableUnits
unusable of
         Left [(UnitInfo, UnusableUnitReason)]
ps     -> forall err val. err -> MaybeErr err val
Failed (PackageFlag -> [(UnitInfo, UnusableUnitReason)] -> UnitErr
PackageFlagErr PackageFlag
flag [(UnitInfo, UnusableUnitReason)]
ps)
         Right (UnitInfo
p:[UnitInfo]
_) -> forall err val. val -> MaybeErr err val
Succeeded VisibilityMap
vm'
          where
           n :: FastString
n = UnitInfo -> FastString
fsPackageName UnitInfo
p

           -- If a user says @-unit-id p[A=<A>]@, this imposes
           -- a requirement on us: whatever our signature A is,
           -- it must fulfill all of p[A=<A>]:A's requirements.
           -- This method is responsible for computing what our
           -- inherited requirements are.
           reqs :: Map ModuleName (Set InstantiatedModule)
reqs | UnitIdArg GenUnit UnitId
orig_uid <- PackageArg
arg = forall {u}.
GenUnit u
-> Map ModuleName (Set (GenModule (GenInstantiatedUnit u)))
collectHoles GenUnit UnitId
orig_uid
                | Bool
otherwise                 = forall k a. Map k a
Map.empty

           collectHoles :: GenUnit u
-> Map ModuleName (Set (GenModule (GenInstantiatedUnit u)))
collectHoles GenUnit u
uid = case GenUnit u
uid of
             GenUnit u
HoleUnit       -> forall k a. Map k a
Map.empty
             RealUnit {}    -> forall k a. Map k a
Map.empty -- definite units don't have holes
             VirtUnit GenInstantiatedUnit u
indef ->
                  let local :: [Map ModuleName (Set (GenModule (GenInstantiatedUnit u)))]
local = [ forall k a. k -> a -> Map k a
Map.singleton
                                  (forall unit. GenModule unit -> ModuleName
moduleName GenModule (GenUnit u)
mod)
                                  (forall a. a -> Set a
Set.singleton forall a b. (a -> b) -> a -> b
$ forall unit. unit -> ModuleName -> GenModule unit
Module GenInstantiatedUnit u
indef ModuleName
mod_name)
                              | (ModuleName
mod_name, GenModule (GenUnit u)
mod) <- forall unit. GenInstantiatedUnit unit -> GenInstantiations unit
instUnitInsts GenInstantiatedUnit u
indef
                              , forall u. GenModule (GenUnit u) -> Bool
isHoleModule GenModule (GenUnit u)
mod ]
                      recurse :: [Map ModuleName (Set (GenModule (GenInstantiatedUnit u)))]
recurse = [ GenUnit u
-> Map ModuleName (Set (GenModule (GenInstantiatedUnit u)))
collectHoles (forall unit. GenModule unit -> unit
moduleUnit GenModule (GenUnit u)
mod)
                                | (ModuleName
_, GenModule (GenUnit u)
mod) <- forall unit. GenInstantiatedUnit unit -> GenInstantiations unit
instUnitInsts GenInstantiatedUnit u
indef ]
                  in forall (f :: * -> *) k a.
(Foldable f, Ord k) =>
(a -> a -> a) -> f (Map k a) -> Map k a
Map.unionsWith forall a. Ord a => Set a -> Set a -> Set a
Set.union forall a b. (a -> b) -> a -> b
$ [Map ModuleName (Set (GenModule (GenInstantiatedUnit u)))]
local forall a. [a] -> [a] -> [a]
++ [Map ModuleName (Set (GenModule (GenInstantiatedUnit u)))]
recurse

           uv :: UnitVisibility
uv = UnitVisibility
                { uv_expose_all :: Bool
uv_expose_all = Bool
b
                , uv_renamings :: [(ModuleName, ModuleName)]
uv_renamings = [(ModuleName, ModuleName)]
rns
                , uv_package_name :: First FastString
uv_package_name = forall a. Maybe a -> First a
First (forall a. a -> Maybe a
Just FastString
n)
                , uv_requirements :: Map ModuleName (Set InstantiatedModule)
uv_requirements = Map ModuleName (Set InstantiatedModule)
reqs
                , uv_explicit :: Bool
uv_explicit = Bool
True
                }
           vm' :: VisibilityMap
vm' = forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Map.insertWith forall a. Monoid a => a -> a -> a
mappend (UnitInfo -> GenUnit UnitId
mkUnit UnitInfo
p) UnitVisibility
uv VisibilityMap
vm_cleared
           -- In the old days, if you said `ghc -package p-0.1 -package p-0.2`
           -- (or if p-0.1 was registered in the pkgdb as exposed: True),
           -- the second package flag would override the first one and you
           -- would only see p-0.2 in exposed modules.  This is good for
           -- usability.
           --
           -- However, with thinning and renaming (or Backpack), there might be
           -- situations where you legitimately want to see two versions of a
           -- package at the same time, and this behavior would make it
           -- impossible to do so.  So we decided that if you pass
           -- -hide-all-packages, this should turn OFF the overriding behavior
           -- where an exposed package hides all other packages with the same
           -- name.  This should not affect Cabal at all, which only ever
           -- exposes one package at a time.
           --
           -- NB: Why a variable no_hide_others?  We have to apply this logic to
           -- -plugin-package too, and it's more consistent if the switch in
           -- behavior is based off of
           -- -hide-all-packages/-hide-all-plugin-packages depending on what
           -- flag is in question.
           vm_cleared :: VisibilityMap
vm_cleared | Bool
no_hide_others = VisibilityMap
vm
                      -- NB: renamings never clear
                      | ((ModuleName, ModuleName)
_:[(ModuleName, ModuleName)]
_) <- [(ModuleName, ModuleName)]
rns = VisibilityMap
vm
                      | Bool
otherwise = forall k a. (k -> a -> Bool) -> Map k a -> Map k a
Map.filterWithKey
                            (\GenUnit UnitId
k UnitVisibility
uv -> GenUnit UnitId
k forall a. Eq a => a -> a -> Bool
== UnitInfo -> GenUnit UnitId
mkUnit UnitInfo
p
                                   Bool -> Bool -> Bool
|| forall a. Maybe a -> First a
First (forall a. a -> Maybe a
Just FastString
n) forall a. Eq a => a -> a -> Bool
/= UnitVisibility -> First FastString
uv_package_name UnitVisibility
uv) VisibilityMap
vm
         Either [(UnitInfo, UnusableUnitReason)] [UnitInfo]
_ -> forall a. String -> a
panic String
"applyPackageFlag"

    HidePackage String
str ->
       case UnitPrecedenceMap
-> UnitInfoMap
-> PreloadUnitClosure
-> PackageArg
-> [UnitInfo]
-> UnusableUnits
-> Either [(UnitInfo, UnusableUnitReason)] [UnitInfo]
findPackages UnitPrecedenceMap
prec_map UnitInfoMap
pkg_map PreloadUnitClosure
closure (String -> PackageArg
PackageArg String
str) [UnitInfo]
pkgs UnusableUnits
unusable of
         Left [(UnitInfo, UnusableUnitReason)]
ps  -> forall err val. err -> MaybeErr err val
Failed (PackageFlag -> [(UnitInfo, UnusableUnitReason)] -> UnitErr
PackageFlagErr PackageFlag
flag [(UnitInfo, UnusableUnitReason)]
ps)
         Right [UnitInfo]
ps -> forall err val. val -> MaybeErr err val
Succeeded forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall k a. Ord k => k -> Map k a -> Map k a
Map.delete) VisibilityMap
vm (forall a b. (a -> b) -> [a] -> [b]
map UnitInfo -> GenUnit UnitId
mkUnit [UnitInfo]
ps)

-- | Like 'selectPackages', but doesn't return a list of unmatched
-- packages.  Furthermore, any packages it returns are *renamed*
-- if the 'UnitArg' has a renaming associated with it.
findPackages :: UnitPrecedenceMap
             -> UnitInfoMap
             -> PreloadUnitClosure
             -> PackageArg -> [UnitInfo]
             -> UnusableUnits
             -> Either [(UnitInfo, UnusableUnitReason)]
                [UnitInfo]
findPackages :: UnitPrecedenceMap
-> UnitInfoMap
-> PreloadUnitClosure
-> PackageArg
-> [UnitInfo]
-> UnusableUnits
-> Either [(UnitInfo, UnusableUnitReason)] [UnitInfo]
findPackages UnitPrecedenceMap
prec_map UnitInfoMap
pkg_map PreloadUnitClosure
closure PackageArg
arg [UnitInfo]
pkgs UnusableUnits
unusable
  = let ps :: [UnitInfo]
ps = forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (PackageArg -> UnitInfo -> Maybe UnitInfo
finder PackageArg
arg) [UnitInfo]
pkgs
    in if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [UnitInfo]
ps
        then forall a b. a -> Either a b
Left (forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (\(UnitInfo
x,UnusableUnitReason
y) -> PackageArg -> UnitInfo -> Maybe UnitInfo
finder PackageArg
arg UnitInfo
x forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \UnitInfo
x' -> forall (m :: * -> *) a. Monad m => a -> m a
return (UnitInfo
x',UnusableUnitReason
y))
                            (forall k a. Map k a -> [a]
Map.elems UnusableUnits
unusable))
        else forall a b. b -> Either a b
Right (UnitPrecedenceMap -> [UnitInfo] -> [UnitInfo]
sortByPreference UnitPrecedenceMap
prec_map [UnitInfo]
ps)
  where
    finder :: PackageArg -> UnitInfo -> Maybe UnitInfo
finder (PackageArg String
str) UnitInfo
p
      = if String -> UnitInfo -> Bool
matchingStr String
str UnitInfo
p
          then forall a. a -> Maybe a
Just UnitInfo
p
          else forall a. Maybe a
Nothing
    finder (UnitIdArg GenUnit UnitId
uid) UnitInfo
p
      = case GenUnit UnitId
uid of
          RealUnit (Definite UnitId
iuid)
            | UnitId
iuid forall a. Eq a => a -> a -> Bool
== forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId UnitInfo
p
            -> forall a. a -> Maybe a
Just UnitInfo
p
          VirtUnit GenInstantiatedUnit UnitId
inst
            | forall unit. Indefinite unit -> unit
indefUnit (forall unit. GenInstantiatedUnit unit -> Indefinite unit
instUnitInstanceOf GenInstantiatedUnit UnitId
inst) forall a. Eq a => a -> a -> Bool
== forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId UnitInfo
p
            -> forall a. a -> Maybe a
Just (UnitInfoMap
-> PreloadUnitClosure
-> [(ModuleName, Module)]
-> UnitInfo
-> UnitInfo
renameUnitInfo UnitInfoMap
pkg_map PreloadUnitClosure
closure (forall unit. GenInstantiatedUnit unit -> GenInstantiations unit
instUnitInsts GenInstantiatedUnit UnitId
inst) UnitInfo
p)
          GenUnit UnitId
_ -> forall a. Maybe a
Nothing

selectPackages :: UnitPrecedenceMap -> PackageArg -> [UnitInfo]
               -> UnusableUnits
               -> Either [(UnitInfo, UnusableUnitReason)]
                  ([UnitInfo], [UnitInfo])
selectPackages :: UnitPrecedenceMap
-> PackageArg
-> [UnitInfo]
-> UnusableUnits
-> Either [(UnitInfo, UnusableUnitReason)] ([UnitInfo], [UnitInfo])
selectPackages UnitPrecedenceMap
prec_map PackageArg
arg [UnitInfo]
pkgs UnusableUnits
unusable
  = let matches :: UnitInfo -> Bool
matches = PackageArg -> UnitInfo -> Bool
matching PackageArg
arg
        ([UnitInfo]
ps,[UnitInfo]
rest) = forall a. (a -> Bool) -> [a] -> ([a], [a])
partition UnitInfo -> Bool
matches [UnitInfo]
pkgs
    in if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [UnitInfo]
ps
        then forall a b. a -> Either a b
Left (forall a. (a -> Bool) -> [a] -> [a]
filter (UnitInfo -> Bool
matchesforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall a b. (a, b) -> a
fst) (forall k a. Map k a -> [a]
Map.elems UnusableUnits
unusable))
        else forall a b. b -> Either a b
Right (UnitPrecedenceMap -> [UnitInfo] -> [UnitInfo]
sortByPreference UnitPrecedenceMap
prec_map [UnitInfo]
ps, [UnitInfo]
rest)

-- | Rename a 'UnitInfo' according to some module instantiation.
renameUnitInfo :: UnitInfoMap -> PreloadUnitClosure -> [(ModuleName, Module)] -> UnitInfo -> UnitInfo
renameUnitInfo :: UnitInfoMap
-> PreloadUnitClosure
-> [(ModuleName, Module)]
-> UnitInfo
-> UnitInfo
renameUnitInfo UnitInfoMap
pkg_map PreloadUnitClosure
closure [(ModuleName, Module)]
insts UnitInfo
conf =
    let hsubst :: UniqFM ModuleName Module
hsubst = forall key elt. Uniquable key => [(key, elt)] -> UniqFM key elt
listToUFM [(ModuleName, Module)]
insts
        smod :: Module -> Module
smod  = UnitInfoMap
-> PreloadUnitClosure
-> UniqFM ModuleName Module
-> Module
-> Module
renameHoleModule' UnitInfoMap
pkg_map PreloadUnitClosure
closure UniqFM ModuleName Module
hsubst
        new_insts :: [(ModuleName, Module)]
new_insts = forall a b. (a -> b) -> [a] -> [b]
map (\(ModuleName
k,Module
v) -> (ModuleName
k,Module -> Module
smod Module
v)) (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [(modulename, mod)]
unitInstantiations UnitInfo
conf)
    in UnitInfo
conf {
        unitInstantiations :: [(ModuleName, Module)]
unitInstantiations = [(ModuleName, Module)]
new_insts,
        unitExposedModules :: [(ModuleName, Maybe Module)]
unitExposedModules = forall a b. (a -> b) -> [a] -> [b]
map (\(ModuleName
mod_name, Maybe Module
mb_mod) -> (ModuleName
mod_name, forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Module -> Module
smod Maybe Module
mb_mod))
                             (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [(modulename, Maybe mod)]
unitExposedModules UnitInfo
conf)
    }


-- A package named on the command line can either include the
-- version, or just the name if it is unambiguous.
matchingStr :: String -> UnitInfo -> Bool
matchingStr :: String -> UnitInfo -> Bool
matchingStr String
str UnitInfo
p
        =  String
str forall a. Eq a => a -> a -> Bool
== forall u. GenUnitInfo u -> String
unitPackageIdString UnitInfo
p
        Bool -> Bool -> Bool
|| String
str forall a. Eq a => a -> a -> Bool
== forall u. GenUnitInfo u -> String
unitPackageNameString UnitInfo
p

matchingId :: UnitId -> UnitInfo -> Bool
matchingId :: UnitId -> UnitInfo -> Bool
matchingId UnitId
uid UnitInfo
p = UnitId
uid forall a. Eq a => a -> a -> Bool
== forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId UnitInfo
p

matching :: PackageArg -> UnitInfo -> Bool
matching :: PackageArg -> UnitInfo -> Bool
matching (PackageArg String
str) = String -> UnitInfo -> Bool
matchingStr String
str
matching (UnitIdArg (RealUnit (Definite UnitId
uid))) = UnitId -> UnitInfo -> Bool
matchingId UnitId
uid
matching (UnitIdArg GenUnit UnitId
_)  = \UnitInfo
_ -> Bool
False -- TODO: warn in this case

-- | This sorts a list of packages, putting "preferred" packages first.
-- See 'compareByPreference' for the semantics of "preference".
sortByPreference :: UnitPrecedenceMap -> [UnitInfo] -> [UnitInfo]
sortByPreference :: UnitPrecedenceMap -> [UnitInfo] -> [UnitInfo]
sortByPreference UnitPrecedenceMap
prec_map = forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (forall a b c. (a -> b -> c) -> b -> a -> c
flip (UnitPrecedenceMap -> UnitInfo -> UnitInfo -> Ordering
compareByPreference UnitPrecedenceMap
prec_map))

-- | Returns 'GT' if @pkg@ should be preferred over @pkg'@ when picking
-- which should be "active".  Here is the order of preference:
--
--      1. First, prefer the latest version
--      2. If the versions are the same, prefer the package that
--      came in the latest package database.
--
-- Pursuant to #12518, we could change this policy to, for example, remove
-- the version preference, meaning that we would always prefer the units
-- in later unit database.
compareByPreference
    :: UnitPrecedenceMap
    -> UnitInfo
    -> UnitInfo
    -> Ordering
compareByPreference :: UnitPrecedenceMap -> UnitInfo -> UnitInfo -> Ordering
compareByPreference UnitPrecedenceMap
prec_map UnitInfo
pkg UnitInfo
pkg'
  = case forall a t. Ord a => (t -> a) -> t -> t -> Ordering
comparing forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Version
unitPackageVersion UnitInfo
pkg UnitInfo
pkg' of
        Ordering
GT -> Ordering
GT
        Ordering
EQ | Just Int
prec  <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId UnitInfo
pkg)  UnitPrecedenceMap
prec_map
           , Just Int
prec' <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId UnitInfo
pkg') UnitPrecedenceMap
prec_map
           -- Prefer the unit from the later DB flag (i.e., higher
           -- precedence)
           -> forall a. Ord a => a -> a -> Ordering
compare Int
prec Int
prec'
           | Bool
otherwise
           -> Ordering
EQ
        Ordering
LT -> Ordering
LT

comparing :: Ord a => (t -> a) -> t -> t -> Ordering
comparing :: forall a t. Ord a => (t -> a) -> t -> t -> Ordering
comparing t -> a
f t
a t
b = t -> a
f t
a forall a. Ord a => a -> a -> Ordering
`compare` t -> a
f t
b

pprFlag :: PackageFlag -> SDoc
pprFlag :: PackageFlag -> SDoc
pprFlag PackageFlag
flag = case PackageFlag
flag of
    HidePackage String
p   -> String -> SDoc
text String
"-hide-package " SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
p
    ExposePackage String
doc PackageArg
_ ModRenaming
_ -> String -> SDoc
text String
doc

pprTrustFlag :: TrustFlag -> SDoc
pprTrustFlag :: TrustFlag -> SDoc
pprTrustFlag TrustFlag
flag = case TrustFlag
flag of
    TrustPackage String
p    -> String -> SDoc
text String
"-trust " SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
p
    DistrustPackage String
p -> String -> SDoc
text String
"-distrust " SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
p

-- -----------------------------------------------------------------------------
-- Wired-in units
--
-- See Note [Wired-in units] in GHC.Unit.Module

type WiringMap = Map UnitId UnitId

findWiredInUnits
   :: (SDoc -> IO ())      -- debug trace
   -> UnitPrecedenceMap
   -> [UnitInfo]           -- database
   -> VisibilityMap             -- info on what units are visible
                                -- for wired in selection
   -> IO ([UnitInfo],  -- unit database updated for wired in
          WiringMap)   -- map from unit id to wired identity

findWiredInUnits :: (SDoc -> IO ())
-> UnitPrecedenceMap
-> [UnitInfo]
-> VisibilityMap
-> IO ([UnitInfo], Map UnitId UnitId)
findWiredInUnits SDoc -> IO ()
printer UnitPrecedenceMap
prec_map [UnitInfo]
pkgs VisibilityMap
vis_map = do
  -- Now we must find our wired-in units, and rename them to
  -- their canonical names (eg. base-1.0 ==> base), as described
  -- in Note [Wired-in units] in GHC.Unit.Module
  let
        matches :: UnitInfo -> UnitId -> Bool
        UnitInfo
pc matches :: UnitInfo -> UnitId -> Bool
`matches` UnitId
pid = forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> srcpkgname
unitPackageName UnitInfo
pc forall a. Eq a => a -> a -> Bool
== FastString -> PackageName
PackageName (UnitId -> FastString
unitIdFS UnitId
pid)

        -- find which package corresponds to each wired-in package
        -- delete any other packages with the same name
        -- update the package and any dependencies to point to the new
        -- one.
        --
        -- When choosing which package to map to a wired-in package
        -- name, we try to pick the latest version of exposed packages.
        -- However, if there are no exposed wired in packages available
        -- (e.g. -hide-all-packages was used), we can't bail: we *have*
        -- to assign a package for the wired-in package: so we try again
        -- with hidden packages included to (and pick the latest
        -- version).
        --
        -- You can also override the default choice by using -ignore-package:
        -- this works even when there is no exposed wired in package
        -- available.
        --
        findWiredInUnit :: [UnitInfo] -> UnitId -> IO (Maybe (UnitId, UnitInfo))
        findWiredInUnit :: [UnitInfo] -> UnitId -> IO (Maybe (UnitId, UnitInfo))
findWiredInUnit [UnitInfo]
pkgs UnitId
wired_pkg =
           let all_ps :: [UnitInfo]
all_ps = [ UnitInfo
p | UnitInfo
p <- [UnitInfo]
pkgs, UnitInfo
p UnitInfo -> UnitId -> Bool
`matches` UnitId
wired_pkg ]
               all_exposed_ps :: [UnitInfo]
all_exposed_ps =
                    [ UnitInfo
p | UnitInfo
p <- [UnitInfo]
all_ps
                        , forall k a. Ord k => k -> Map k a -> Bool
Map.member (UnitInfo -> GenUnit UnitId
mkUnit UnitInfo
p) VisibilityMap
vis_map ] in
           case [UnitInfo]
all_exposed_ps of
            [] -> case [UnitInfo]
all_ps of
                       []   -> IO (Maybe (UnitId, UnitInfo))
notfound
                       [UnitInfo]
many -> UnitInfo -> IO (Maybe (UnitId, UnitInfo))
pick (forall a. [a] -> a
head (UnitPrecedenceMap -> [UnitInfo] -> [UnitInfo]
sortByPreference UnitPrecedenceMap
prec_map [UnitInfo]
many))
            [UnitInfo]
many -> UnitInfo -> IO (Maybe (UnitId, UnitInfo))
pick (forall a. [a] -> a
head (UnitPrecedenceMap -> [UnitInfo] -> [UnitInfo]
sortByPreference UnitPrecedenceMap
prec_map [UnitInfo]
many))
          where
                notfound :: IO (Maybe (UnitId, UnitInfo))
notfound = do
                          SDoc -> IO ()
printer forall a b. (a -> b) -> a -> b
$
                            String -> SDoc
text String
"wired-in package "
                                 SDoc -> SDoc -> SDoc
<> FastString -> SDoc
ftext (UnitId -> FastString
unitIdFS UnitId
wired_pkg)
                                 SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
" not found."
                          forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
                pick :: UnitInfo -> IO (Maybe (UnitId, UnitInfo))
                pick :: UnitInfo -> IO (Maybe (UnitId, UnitInfo))
pick UnitInfo
pkg = do
                        SDoc -> IO ()
printer forall a b. (a -> b) -> a -> b
$
                            String -> SDoc
text String
"wired-in package "
                                 SDoc -> SDoc -> SDoc
<> FastString -> SDoc
ftext (UnitId -> FastString
unitIdFS UnitId
wired_pkg)
                                 SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
" mapped to "
                                 SDoc -> SDoc -> SDoc
<> forall a. Outputable a => a -> SDoc
ppr (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId UnitInfo
pkg)
                        forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just (UnitId
wired_pkg, UnitInfo
pkg))


  [Maybe (UnitId, UnitInfo)]
mb_wired_in_pkgs <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ([UnitInfo] -> UnitId -> IO (Maybe (UnitId, UnitInfo))
findWiredInUnit [UnitInfo]
pkgs) [UnitId]
wiredInUnitIds
  let
        wired_in_pkgs :: [(UnitId, UnitInfo)]
wired_in_pkgs = forall a. [Maybe a] -> [a]
catMaybes [Maybe (UnitId, UnitInfo)]
mb_wired_in_pkgs

        wiredInMap :: Map UnitId UnitId
        wiredInMap :: Map UnitId UnitId
wiredInMap = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
          [ (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId UnitInfo
realUnitInfo, UnitId
wiredInUnitId)
          | (UnitId
wiredInUnitId, UnitInfo
realUnitInfo) <- [(UnitId, UnitInfo)]
wired_in_pkgs
          , Bool -> Bool
not (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Bool
unitIsIndefinite UnitInfo
realUnitInfo)
          ]

        updateWiredInDependencies :: [GenericUnitInfo
   (f UnitId) srcpkgid srcpkgname UnitId modulename Module]
-> [GenericUnitInfo
      (f UnitId) srcpkgid srcpkgname UnitId modulename Module]
updateWiredInDependencies [GenericUnitInfo
   (f UnitId) srcpkgid srcpkgname UnitId modulename Module]
pkgs = forall a b. (a -> b) -> [a] -> [b]
map (forall {compid} {srcpkgid} {srcpkgname} {modulename}.
GenericUnitInfo compid srcpkgid srcpkgname UnitId modulename Module
-> GenericUnitInfo
     compid srcpkgid srcpkgname UnitId modulename Module
upd_deps forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {f :: * -> *} {srcpkgid} {srcpkgname} {modulename} {mod}.
Functor f =>
GenericUnitInfo
  (f UnitId) srcpkgid srcpkgname UnitId modulename mod
-> GenericUnitInfo
     (f UnitId) srcpkgid srcpkgname UnitId modulename mod
upd_pkg) [GenericUnitInfo
   (f UnitId) srcpkgid srcpkgname UnitId modulename Module]
pkgs
          where upd_pkg :: GenericUnitInfo
  (f UnitId) srcpkgid srcpkgname UnitId modulename mod
-> GenericUnitInfo
     (f UnitId) srcpkgid srcpkgname UnitId modulename mod
upd_pkg GenericUnitInfo
  (f UnitId) srcpkgid srcpkgname UnitId modulename mod
pkg
                  | Just UnitId
wiredInUnitId <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId GenericUnitInfo
  (f UnitId) srcpkgid srcpkgname UnitId modulename mod
pkg) Map UnitId UnitId
wiredInMap
                  = GenericUnitInfo
  (f UnitId) srcpkgid srcpkgname UnitId modulename mod
pkg { unitId :: UnitId
unitId         = UnitId
wiredInUnitId
                        , unitInstanceOf :: f UnitId
unitInstanceOf = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a b. a -> b -> a
const UnitId
wiredInUnitId) (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> compid
unitInstanceOf GenericUnitInfo
  (f UnitId) srcpkgid srcpkgname UnitId modulename mod
pkg)
                           -- every non instantiated unit is an instance of
                           -- itself (required by Backpack...)
                           --
                           -- See Note [About Units] in GHC.Unit
                        }
                  | Bool
otherwise
                  = GenericUnitInfo
  (f UnitId) srcpkgid srcpkgname UnitId modulename mod
pkg
                upd_deps :: GenericUnitInfo compid srcpkgid srcpkgname UnitId modulename Module
-> GenericUnitInfo
     compid srcpkgid srcpkgname UnitId modulename Module
upd_deps GenericUnitInfo compid srcpkgid srcpkgname UnitId modulename Module
pkg = GenericUnitInfo compid srcpkgid srcpkgname UnitId modulename Module
pkg {
                      unitDepends :: [UnitId]
unitDepends = forall a b. (a -> b) -> [a] -> [b]
map (Map UnitId UnitId -> UnitId -> UnitId
upd_wired_in Map UnitId UnitId
wiredInMap) (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [uid]
unitDepends GenericUnitInfo compid srcpkgid srcpkgname UnitId modulename Module
pkg),
                      unitExposedModules :: [(modulename, Maybe Module)]
unitExposedModules
                        = forall a b. (a -> b) -> [a] -> [b]
map (\(modulename
k,Maybe Module
v) -> (modulename
k, forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Map UnitId UnitId -> Module -> Module
upd_wired_in_mod Map UnitId UnitId
wiredInMap) Maybe Module
v))
                              (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [(modulename, Maybe mod)]
unitExposedModules GenericUnitInfo compid srcpkgid srcpkgname UnitId modulename Module
pkg)
                    }


  forall (m :: * -> *) a. Monad m => a -> m a
return (forall {f :: * -> *} {srcpkgid} {srcpkgname} {modulename}.
Functor f =>
[GenericUnitInfo
   (f UnitId) srcpkgid srcpkgname UnitId modulename Module]
-> [GenericUnitInfo
      (f UnitId) srcpkgid srcpkgname UnitId modulename Module]
updateWiredInDependencies [UnitInfo]
pkgs, Map UnitId UnitId
wiredInMap)

-- Helper functions for rewiring Module and Unit.  These
-- rewrite Units of modules in wired-in packages to the form known to the
-- compiler, as described in Note [Wired-in units] in GHC.Unit.Module.
--
-- For instance, base-4.9.0.0 will be rewritten to just base, to match
-- what appears in GHC.Builtin.Names.

upd_wired_in_mod :: WiringMap -> Module -> Module
upd_wired_in_mod :: Map UnitId UnitId -> Module -> Module
upd_wired_in_mod Map UnitId UnitId
wiredInMap (Module GenUnit UnitId
uid ModuleName
m) = forall unit. unit -> ModuleName -> GenModule unit
Module (Map UnitId UnitId -> GenUnit UnitId -> GenUnit UnitId
upd_wired_in_uid Map UnitId UnitId
wiredInMap GenUnit UnitId
uid) ModuleName
m

upd_wired_in_uid :: WiringMap -> Unit -> Unit
upd_wired_in_uid :: Map UnitId UnitId -> GenUnit UnitId -> GenUnit UnitId
upd_wired_in_uid Map UnitId UnitId
wiredInMap GenUnit UnitId
u = case GenUnit UnitId
u of
   GenUnit UnitId
HoleUnit                -> forall uid. GenUnit uid
HoleUnit
   RealUnit (Definite UnitId
uid) -> forall uid. Definite uid -> GenUnit uid
RealUnit (forall unit. unit -> Definite unit
Definite (Map UnitId UnitId -> UnitId -> UnitId
upd_wired_in Map UnitId UnitId
wiredInMap UnitId
uid))
   VirtUnit GenInstantiatedUnit UnitId
indef_uid ->
      forall uid. GenInstantiatedUnit uid -> GenUnit uid
VirtUnit forall a b. (a -> b) -> a -> b
$ forall u.
IsUnitId u =>
Indefinite u -> GenInstantiations u -> GenInstantiatedUnit u
mkInstantiatedUnit
        (forall unit. GenInstantiatedUnit unit -> Indefinite unit
instUnitInstanceOf GenInstantiatedUnit UnitId
indef_uid)
        (forall a b. (a -> b) -> [a] -> [b]
map (\(ModuleName
x,Module
y) -> (ModuleName
x,Map UnitId UnitId -> Module -> Module
upd_wired_in_mod Map UnitId UnitId
wiredInMap Module
y)) (forall unit. GenInstantiatedUnit unit -> GenInstantiations unit
instUnitInsts GenInstantiatedUnit UnitId
indef_uid))

upd_wired_in :: WiringMap -> UnitId -> UnitId
upd_wired_in :: Map UnitId UnitId -> UnitId -> UnitId
upd_wired_in Map UnitId UnitId
wiredInMap UnitId
key
    | Just UnitId
key' <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UnitId
key Map UnitId UnitId
wiredInMap = UnitId
key'
    | Bool
otherwise = UnitId
key

updateVisibilityMap :: WiringMap -> VisibilityMap -> VisibilityMap
updateVisibilityMap :: Map UnitId UnitId -> VisibilityMap -> VisibilityMap
updateVisibilityMap Map UnitId UnitId
wiredInMap VisibilityMap
vis_map = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' VisibilityMap -> (UnitId, UnitId) -> VisibilityMap
f VisibilityMap
vis_map (forall k a. Map k a -> [(k, a)]
Map.toList Map UnitId UnitId
wiredInMap)
  where f :: VisibilityMap -> (UnitId, UnitId) -> VisibilityMap
f VisibilityMap
vm (UnitId
from, UnitId
to) = case forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (forall uid. Definite uid -> GenUnit uid
RealUnit (forall unit. unit -> Definite unit
Definite UnitId
from)) VisibilityMap
vis_map of
                    Maybe UnitVisibility
Nothing -> VisibilityMap
vm
                    Just UnitVisibility
r -> forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (forall uid. Definite uid -> GenUnit uid
RealUnit (forall unit. unit -> Definite unit
Definite UnitId
to)) UnitVisibility
r
                                (forall k a. Ord k => k -> Map k a -> Map k a
Map.delete (forall uid. Definite uid -> GenUnit uid
RealUnit (forall unit. unit -> Definite unit
Definite UnitId
from)) VisibilityMap
vm)


-- ----------------------------------------------------------------------------

-- | The reason why a unit is unusable.
data UnusableUnitReason
  = -- | We ignored it explicitly using @-ignore-package@.
    IgnoredWithFlag
    -- | This unit transitively depends on a unit that was never present
    -- in any of the provided databases.
  | BrokenDependencies   [UnitId]
    -- | This unit transitively depends on a unit involved in a cycle.
    -- Note that the list of 'UnitId' reports the direct dependencies
    -- of this unit that (transitively) depended on the cycle, and not
    -- the actual cycle itself (which we report separately at high verbosity.)
  | CyclicDependencies   [UnitId]
    -- | This unit transitively depends on a unit which was ignored.
  | IgnoredDependencies  [UnitId]
    -- | This unit transitively depends on a unit which was
    -- shadowed by an ABI-incompatible unit.
  | ShadowedDependencies [UnitId]

instance Outputable UnusableUnitReason where
    ppr :: UnusableUnitReason -> SDoc
ppr UnusableUnitReason
IgnoredWithFlag = String -> SDoc
text String
"[ignored with flag]"
    ppr (BrokenDependencies [UnitId]
uids)   = SDoc -> SDoc
brackets (String -> SDoc
text String
"broken" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr [UnitId]
uids)
    ppr (CyclicDependencies [UnitId]
uids)   = SDoc -> SDoc
brackets (String -> SDoc
text String
"cyclic" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr [UnitId]
uids)
    ppr (IgnoredDependencies [UnitId]
uids)  = SDoc -> SDoc
brackets (String -> SDoc
text String
"ignored" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr [UnitId]
uids)
    ppr (ShadowedDependencies [UnitId]
uids) = SDoc -> SDoc
brackets (String -> SDoc
text String
"shadowed" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr [UnitId]
uids)

type UnusableUnits = Map UnitId (UnitInfo, UnusableUnitReason)

pprReason :: SDoc -> UnusableUnitReason -> SDoc
pprReason :: SDoc -> UnusableUnitReason -> SDoc
pprReason SDoc
pref UnusableUnitReason
reason = case UnusableUnitReason
reason of
  UnusableUnitReason
IgnoredWithFlag ->
      SDoc
pref SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"ignored due to an -ignore-package flag"
  BrokenDependencies [UnitId]
deps ->
      SDoc
pref SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"unusable due to missing dependencies:" SDoc -> SDoc -> SDoc
$$
        Int -> SDoc -> SDoc
nest Int
2 ([SDoc] -> SDoc
hsep (forall a b. (a -> b) -> [a] -> [b]
map forall a. Outputable a => a -> SDoc
ppr [UnitId]
deps))
  CyclicDependencies [UnitId]
deps ->
      SDoc
pref SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"unusable due to cyclic dependencies:" SDoc -> SDoc -> SDoc
$$
        Int -> SDoc -> SDoc
nest Int
2 ([SDoc] -> SDoc
hsep (forall a b. (a -> b) -> [a] -> [b]
map forall a. Outputable a => a -> SDoc
ppr [UnitId]
deps))
  IgnoredDependencies [UnitId]
deps ->
      SDoc
pref SDoc -> SDoc -> SDoc
<+> String -> SDoc
text (String
"unusable because the -ignore-package flag was used to " forall a. [a] -> [a] -> [a]
++
                     String
"ignore at least one of its dependencies:") SDoc -> SDoc -> SDoc
$$
        Int -> SDoc -> SDoc
nest Int
2 ([SDoc] -> SDoc
hsep (forall a b. (a -> b) -> [a] -> [b]
map forall a. Outputable a => a -> SDoc
ppr [UnitId]
deps))
  ShadowedDependencies [UnitId]
deps ->
      SDoc
pref SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"unusable due to shadowed dependencies:" SDoc -> SDoc -> SDoc
$$
        Int -> SDoc -> SDoc
nest Int
2 ([SDoc] -> SDoc
hsep (forall a b. (a -> b) -> [a] -> [b]
map forall a. Outputable a => a -> SDoc
ppr [UnitId]
deps))

reportCycles :: (SDoc -> IO ()) -> [SCC UnitInfo] -> IO ()
reportCycles :: (SDoc -> IO ()) -> [SCC UnitInfo] -> IO ()
reportCycles SDoc -> IO ()
printer [SCC UnitInfo]
sccs = forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ SCC UnitInfo -> IO ()
report [SCC UnitInfo]
sccs
  where
    report :: SCC UnitInfo -> IO ()
report (AcyclicSCC UnitInfo
_) = forall (m :: * -> *) a. Monad m => a -> m a
return ()
    report (CyclicSCC [UnitInfo]
vs) =
        SDoc -> IO ()
printer forall a b. (a -> b) -> a -> b
$
          String -> SDoc
text String
"these packages are involved in a cycle:" SDoc -> SDoc -> SDoc
$$
            Int -> SDoc -> SDoc
nest Int
2 ([SDoc] -> SDoc
hsep (forall a b. (a -> b) -> [a] -> [b]
map (forall a. Outputable a => a -> SDoc
ppr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId) [UnitInfo]
vs))

reportUnusable :: (SDoc -> IO ()) -> UnusableUnits -> IO ()
reportUnusable :: (SDoc -> IO ()) -> UnusableUnits -> IO ()
reportUnusable SDoc -> IO ()
printer UnusableUnits
pkgs = forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (UnitId, (UnitInfo, UnusableUnitReason)) -> IO ()
report (forall k a. Map k a -> [(k, a)]
Map.toList UnusableUnits
pkgs)
  where
    report :: (UnitId, (UnitInfo, UnusableUnitReason)) -> IO ()
report (UnitId
ipid, (UnitInfo
_, UnusableUnitReason
reason)) =
       SDoc -> IO ()
printer forall a b. (a -> b) -> a -> b
$
         SDoc -> UnusableUnitReason -> SDoc
pprReason
           (String -> SDoc
text String
"package" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr UnitId
ipid SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"is") UnusableUnitReason
reason

-- ----------------------------------------------------------------------------
--
-- Utilities on the database
--

-- | A reverse dependency index, mapping an 'UnitId' to
-- the 'UnitId's which have a dependency on it.
type RevIndex = Map UnitId [UnitId]

-- | Compute the reverse dependency index of a unit database.
reverseDeps :: UnitInfoMap -> RevIndex
reverseDeps :: UnitInfoMap -> RevIndex
reverseDeps UnitInfoMap
db = forall a b k. (a -> b -> a) -> a -> Map k b -> a
Map.foldl' forall {a} {compid} {srcpkgid} {srcpkgname} {modulename} {mod}.
Ord a =>
Map a [a]
-> GenericUnitInfo compid srcpkgid srcpkgname a modulename mod
-> Map a [a]
go forall k a. Map k a
Map.empty UnitInfoMap
db
  where
    go :: Map a [a]
-> GenericUnitInfo compid srcpkgid srcpkgname a modulename mod
-> Map a [a]
go Map a [a]
r GenericUnitInfo compid srcpkgid srcpkgname a modulename mod
pkg = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (forall {k} {a}. Ord k => a -> Map k [a] -> k -> Map k [a]
go' (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId GenericUnitInfo compid srcpkgid srcpkgname a modulename mod
pkg)) Map a [a]
r (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [uid]
unitDepends GenericUnitInfo compid srcpkgid srcpkgname a modulename mod
pkg)
    go' :: a -> Map k [a] -> k -> Map k [a]
go' a
from Map k [a]
r k
to = forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Map.insertWith forall a. [a] -> [a] -> [a]
(++) k
to [a
from] Map k [a]
r

-- | Given a list of 'UnitId's to remove, a database,
-- and a reverse dependency index (as computed by 'reverseDeps'),
-- remove those units, plus any units which depend on them.
-- Returns the pruned database, as well as a list of 'UnitInfo's
-- that was removed.
removeUnits :: [UnitId] -> RevIndex
               -> UnitInfoMap
               -> (UnitInfoMap, [UnitInfo])
removeUnits :: [UnitId] -> RevIndex -> UnitInfoMap -> (UnitInfoMap, [UnitInfo])
removeUnits [UnitId]
uids RevIndex
index UnitInfoMap
m = [UnitId] -> (UnitInfoMap, [UnitInfo]) -> (UnitInfoMap, [UnitInfo])
go [UnitId]
uids (UnitInfoMap
m,[])
  where
    go :: [UnitId] -> (UnitInfoMap, [UnitInfo]) -> (UnitInfoMap, [UnitInfo])
go [] (UnitInfoMap
m,[UnitInfo]
pkgs) = (UnitInfoMap
m,[UnitInfo]
pkgs)
    go (UnitId
uid:[UnitId]
uids) (UnitInfoMap
m,[UnitInfo]
pkgs)
        | Just UnitInfo
pkg <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UnitId
uid UnitInfoMap
m
        = case forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UnitId
uid RevIndex
index of
            Maybe [UnitId]
Nothing    -> [UnitId] -> (UnitInfoMap, [UnitInfo]) -> (UnitInfoMap, [UnitInfo])
go [UnitId]
uids (forall k a. Ord k => k -> Map k a -> Map k a
Map.delete UnitId
uid UnitInfoMap
m, UnitInfo
pkgforall a. a -> [a] -> [a]
:[UnitInfo]
pkgs)
            Just [UnitId]
rdeps -> [UnitId] -> (UnitInfoMap, [UnitInfo]) -> (UnitInfoMap, [UnitInfo])
go ([UnitId]
rdeps forall a. [a] -> [a] -> [a]
++ [UnitId]
uids) (forall k a. Ord k => k -> Map k a -> Map k a
Map.delete UnitId
uid UnitInfoMap
m, UnitInfo
pkgforall a. a -> [a] -> [a]
:[UnitInfo]
pkgs)
        | Bool
otherwise
        = [UnitId] -> (UnitInfoMap, [UnitInfo]) -> (UnitInfoMap, [UnitInfo])
go [UnitId]
uids (UnitInfoMap
m,[UnitInfo]
pkgs)

-- | Given a 'UnitInfo' from some 'UnitInfoMap', return all entries in 'depends'
-- which correspond to units that do not exist in the index.
depsNotAvailable :: UnitInfoMap
                 -> UnitInfo
                 -> [UnitId]
depsNotAvailable :: UnitInfoMap -> UnitInfo -> [UnitId]
depsNotAvailable UnitInfoMap
pkg_map UnitInfo
pkg = forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall k a. Ord k => k -> Map k a -> Bool
`Map.member` UnitInfoMap
pkg_map)) (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [uid]
unitDepends UnitInfo
pkg)

-- | Given a 'UnitInfo' from some 'UnitInfoMap' return all entries in
-- 'unitAbiDepends' which correspond to units that do not exist, OR have
-- mismatching ABIs.
depsAbiMismatch :: UnitInfoMap
                -> UnitInfo
                -> [UnitId]
depsAbiMismatch :: UnitInfoMap -> UnitInfo -> [UnitId]
depsAbiMismatch UnitInfoMap
pkg_map UnitInfo
pkg = forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UnitId, ShortText) -> Bool
abiMatch) forall a b. (a -> b) -> a -> b
$ forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [(uid, ShortText)]
unitAbiDepends UnitInfo
pkg
  where
    abiMatch :: (UnitId, ShortText) -> Bool
abiMatch (UnitId
dep_uid, ShortText
abi)
        | Just UnitInfo
dep_pkg <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UnitId
dep_uid UnitInfoMap
pkg_map
        = forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> ShortText
unitAbiHash UnitInfo
dep_pkg forall a. Eq a => a -> a -> Bool
== ShortText
abi
        | Bool
otherwise
        = Bool
False

-- -----------------------------------------------------------------------------
-- Ignore units

ignoreUnits :: [IgnorePackageFlag] -> [UnitInfo] -> UnusableUnits
ignoreUnits :: [IgnorePackageFlag] -> [UnitInfo] -> UnusableUnits
ignoreUnits [IgnorePackageFlag]
flags [UnitInfo]
pkgs = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap IgnorePackageFlag -> [(UnitId, (UnitInfo, UnusableUnitReason))]
doit [IgnorePackageFlag]
flags)
  where
  doit :: IgnorePackageFlag -> [(UnitId, (UnitInfo, UnusableUnitReason))]
doit (IgnorePackage String
str) =
     case forall a. (a -> Bool) -> [a] -> ([a], [a])
partition (String -> UnitInfo -> Bool
matchingStr String
str) [UnitInfo]
pkgs of
         ([UnitInfo]
ps, [UnitInfo]
_) -> [ (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId UnitInfo
p, (UnitInfo
p, UnusableUnitReason
IgnoredWithFlag))
                    | UnitInfo
p <- [UnitInfo]
ps ]
        -- missing unit is not an error for -ignore-package,
        -- because a common usage is to -ignore-package P as
        -- a preventative measure just in case P exists.

-- ----------------------------------------------------------------------------
--
-- Merging databases
--

-- | For each unit, a mapping from uid -> i indicates that this
-- unit was brought into GHC by the ith @-package-db@ flag on
-- the command line.  We use this mapping to make sure we prefer
-- units that were defined later on the command line, if there
-- is an ambiguity.
type UnitPrecedenceMap = Map UnitId Int

-- | Given a list of databases, merge them together, where
-- units with the same unit id in later databases override
-- earlier ones.  This does NOT check if the resulting database
-- makes sense (that's done by 'validateDatabase').
mergeDatabases :: (SDoc -> IO ()) -> [UnitDatabase UnitId]
               -> IO (UnitInfoMap, UnitPrecedenceMap)
mergeDatabases :: (SDoc -> IO ())
-> [UnitDatabase UnitId] -> IO (UnitInfoMap, UnitPrecedenceMap)
mergeDatabases SDoc -> IO ()
printer = forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (UnitInfoMap, UnitPrecedenceMap)
-> (Int, UnitDatabase UnitId)
-> IO (UnitInfoMap, UnitPrecedenceMap)
merge (forall k a. Map k a
Map.empty, forall k a. Map k a
Map.empty) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. [a] -> [b] -> [(a, b)]
zip [Int
1..]
  where
    merge :: (UnitInfoMap, UnitPrecedenceMap)
-> (Int, UnitDatabase UnitId)
-> IO (UnitInfoMap, UnitPrecedenceMap)
merge (UnitInfoMap
pkg_map, UnitPrecedenceMap
prec_map) (Int
i, UnitDatabase String
db_path [UnitInfo]
db) = do
      SDoc -> IO ()
printer forall a b. (a -> b) -> a -> b
$
          String -> SDoc
text String
"loading package database" SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
db_path
      forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (forall a. Set a -> [a]
Set.toList Set UnitId
override_set) forall a b. (a -> b) -> a -> b
$ \UnitId
pkg ->
          SDoc -> IO ()
printer forall a b. (a -> b) -> a -> b
$
              String -> SDoc
text String
"package" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr UnitId
pkg SDoc -> SDoc -> SDoc
<+>
              String -> SDoc
text String
"overrides a previously defined package"
      forall (m :: * -> *) a. Monad m => a -> m a
return (UnitInfoMap
pkg_map', UnitPrecedenceMap
prec_map')
     where
      db_map :: UnitInfoMap
db_map = forall {compid} {srcpkgid} {srcpkgname} {modulename} {mod}.
[GenericUnitInfo compid srcpkgid srcpkgname UnitId modulename mod]
-> Map
     UnitId
     (GenericUnitInfo compid srcpkgid srcpkgname UnitId modulename mod)
mk_pkg_map [UnitInfo]
db
      mk_pkg_map :: [GenericUnitInfo compid srcpkgid srcpkgname UnitId modulename mod]
-> Map
     UnitId
     (GenericUnitInfo compid srcpkgid srcpkgname UnitId modulename mod)
mk_pkg_map = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (\GenericUnitInfo compid srcpkgid srcpkgname UnitId modulename mod
p -> (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId GenericUnitInfo compid srcpkgid srcpkgname UnitId modulename mod
p, GenericUnitInfo compid srcpkgid srcpkgname UnitId modulename mod
p))

      -- The set of UnitIds which appear in both db and pkgs.  These are the
      -- ones that get overridden.  Compute this just to give some
      -- helpful debug messages at -v2
      override_set :: Set UnitId
      override_set :: Set UnitId
override_set = forall a. Ord a => Set a -> Set a -> Set a
Set.intersection (forall k a. Map k a -> Set k
Map.keysSet UnitInfoMap
db_map)
                                      (forall k a. Map k a -> Set k
Map.keysSet UnitInfoMap
pkg_map)

      -- Now merge the sets together (NB: in case of duplicate,
      -- first argument preferred)
      pkg_map' :: UnitInfoMap
      pkg_map' :: UnitInfoMap
pkg_map' = forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union UnitInfoMap
db_map UnitInfoMap
pkg_map

      prec_map' :: UnitPrecedenceMap
      prec_map' :: UnitPrecedenceMap
prec_map' = forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union (forall a b k. (a -> b) -> Map k a -> Map k b
Map.map (forall a b. a -> b -> a
const Int
i) UnitInfoMap
db_map) UnitPrecedenceMap
prec_map

-- | Validates a database, removing unusable units from it
-- (this includes removing units that the user has explicitly
-- ignored.)  Our general strategy:
--
-- 1. Remove all broken units (dangling dependencies)
-- 2. Remove all units that are cyclic
-- 3. Apply ignore flags
-- 4. Remove all units which have deps with mismatching ABIs
--
validateDatabase :: UnitConfig -> UnitInfoMap
                 -> (UnitInfoMap, UnusableUnits, [SCC UnitInfo])
validateDatabase :: UnitConfig
-> UnitInfoMap -> (UnitInfoMap, UnusableUnits, [SCC UnitInfo])
validateDatabase UnitConfig
cfg UnitInfoMap
pkg_map1 =
    (UnitInfoMap
pkg_map5, UnusableUnits
unusable, [SCC UnitInfo]
sccs)
  where
    ignore_flags :: [IgnorePackageFlag]
ignore_flags = forall a. [a] -> [a]
reverse (UnitConfig -> [IgnorePackageFlag]
unitConfigFlagsIgnored UnitConfig
cfg)

    -- Compute the reverse dependency index
    index :: RevIndex
index = UnitInfoMap -> RevIndex
reverseDeps UnitInfoMap
pkg_map1

    -- Helper function
    mk_unusable :: (t -> b)
-> (t
    -> GenericUnitInfo compid srcpkgid srcpkgname k modulename mod
    -> t)
-> t
-> [GenericUnitInfo compid srcpkgid srcpkgname k modulename mod]
-> Map
     k (GenericUnitInfo compid srcpkgid srcpkgname k modulename mod, b)
mk_unusable t -> b
mk_err t
-> GenericUnitInfo compid srcpkgid srcpkgname k modulename mod -> t
dep_matcher t
m [GenericUnitInfo compid srcpkgid srcpkgname k modulename mod]
uids =
      forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [ (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId GenericUnitInfo compid srcpkgid srcpkgname k modulename mod
pkg, (GenericUnitInfo compid srcpkgid srcpkgname k modulename mod
pkg, t -> b
mk_err (t
-> GenericUnitInfo compid srcpkgid srcpkgname k modulename mod -> t
dep_matcher t
m GenericUnitInfo compid srcpkgid srcpkgname k modulename mod
pkg)))
                   | GenericUnitInfo compid srcpkgid srcpkgname k modulename mod
pkg <- [GenericUnitInfo compid srcpkgid srcpkgname k modulename mod]
uids ]

    -- Find broken units
    directly_broken :: [UnitInfo]
directly_broken = forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnitInfoMap -> UnitInfo -> [UnitId]
depsNotAvailable UnitInfoMap
pkg_map1)
                             (forall k a. Map k a -> [a]
Map.elems UnitInfoMap
pkg_map1)
    (UnitInfoMap
pkg_map2, [UnitInfo]
broken) = [UnitId] -> RevIndex -> UnitInfoMap -> (UnitInfoMap, [UnitInfo])
removeUnits (forall a b. (a -> b) -> [a] -> [b]
map forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId [UnitInfo]
directly_broken) RevIndex
index UnitInfoMap
pkg_map1
    unusable_broken :: UnusableUnits
unusable_broken = forall {k} {t} {b} {t} {compid} {srcpkgid} {srcpkgname}
       {modulename} {mod}.
Ord k =>
(t -> b)
-> (t
    -> GenericUnitInfo compid srcpkgid srcpkgname k modulename mod
    -> t)
-> t
-> [GenericUnitInfo compid srcpkgid srcpkgname k modulename mod]
-> Map
     k (GenericUnitInfo compid srcpkgid srcpkgname k modulename mod, b)
mk_unusable [UnitId] -> UnusableUnitReason
BrokenDependencies UnitInfoMap -> UnitInfo -> [UnitId]
depsNotAvailable UnitInfoMap
pkg_map2 [UnitInfo]
broken

    -- Find recursive units
    sccs :: [SCC UnitInfo]
sccs = forall key node. Ord key => [(node, key, [key])] -> [SCC node]
stronglyConnComp [ (UnitInfo
pkg, forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId UnitInfo
pkg, forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [uid]
unitDepends UnitInfo
pkg)
                            | UnitInfo
pkg <- forall k a. Map k a -> [a]
Map.elems UnitInfoMap
pkg_map2 ]
    getCyclicSCC :: SCC (GenericUnitInfo compid srcpkgid srcpkgname b modulename mod)
-> [b]
getCyclicSCC (CyclicSCC [GenericUnitInfo compid srcpkgid srcpkgname b modulename mod]
vs) = forall a b. (a -> b) -> [a] -> [b]
map forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId [GenericUnitInfo compid srcpkgid srcpkgname b modulename mod]
vs
    getCyclicSCC (AcyclicSCC GenericUnitInfo compid srcpkgid srcpkgname b modulename mod
_) = []
    (UnitInfoMap
pkg_map3, [UnitInfo]
cyclic) = [UnitId] -> RevIndex -> UnitInfoMap -> (UnitInfoMap, [UnitInfo])
removeUnits (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall {compid} {srcpkgid} {srcpkgname} {b} {modulename} {mod}.
SCC (GenericUnitInfo compid srcpkgid srcpkgname b modulename mod)
-> [b]
getCyclicSCC [SCC UnitInfo]
sccs) RevIndex
index UnitInfoMap
pkg_map2
    unusable_cyclic :: UnusableUnits
unusable_cyclic = forall {k} {t} {b} {t} {compid} {srcpkgid} {srcpkgname}
       {modulename} {mod}.
Ord k =>
(t -> b)
-> (t
    -> GenericUnitInfo compid srcpkgid srcpkgname k modulename mod
    -> t)
-> t
-> [GenericUnitInfo compid srcpkgid srcpkgname k modulename mod]
-> Map
     k (GenericUnitInfo compid srcpkgid srcpkgname k modulename mod, b)
mk_unusable [UnitId] -> UnusableUnitReason
CyclicDependencies UnitInfoMap -> UnitInfo -> [UnitId]
depsNotAvailable UnitInfoMap
pkg_map3 [UnitInfo]
cyclic

    -- Apply ignore flags
    directly_ignored :: UnusableUnits
directly_ignored = [IgnorePackageFlag] -> [UnitInfo] -> UnusableUnits
ignoreUnits [IgnorePackageFlag]
ignore_flags (forall k a. Map k a -> [a]
Map.elems UnitInfoMap
pkg_map3)
    (UnitInfoMap
pkg_map4, [UnitInfo]
ignored) = [UnitId] -> RevIndex -> UnitInfoMap -> (UnitInfoMap, [UnitInfo])
removeUnits (forall k a. Map k a -> [k]
Map.keys UnusableUnits
directly_ignored) RevIndex
index UnitInfoMap
pkg_map3
    unusable_ignored :: UnusableUnits
unusable_ignored = forall {k} {t} {b} {t} {compid} {srcpkgid} {srcpkgname}
       {modulename} {mod}.
Ord k =>
(t -> b)
-> (t
    -> GenericUnitInfo compid srcpkgid srcpkgname k modulename mod
    -> t)
-> t
-> [GenericUnitInfo compid srcpkgid srcpkgname k modulename mod]
-> Map
     k (GenericUnitInfo compid srcpkgid srcpkgname k modulename mod, b)
mk_unusable [UnitId] -> UnusableUnitReason
IgnoredDependencies UnitInfoMap -> UnitInfo -> [UnitId]
depsNotAvailable UnitInfoMap
pkg_map4 [UnitInfo]
ignored

    -- Knock out units whose dependencies don't agree with ABI
    -- (i.e., got invalidated due to shadowing)
    directly_shadowed :: [UnitInfo]
directly_shadowed = forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnitInfoMap -> UnitInfo -> [UnitId]
depsAbiMismatch UnitInfoMap
pkg_map4)
                               (forall k a. Map k a -> [a]
Map.elems UnitInfoMap
pkg_map4)
    (UnitInfoMap
pkg_map5, [UnitInfo]
shadowed) = [UnitId] -> RevIndex -> UnitInfoMap -> (UnitInfoMap, [UnitInfo])
removeUnits (forall a b. (a -> b) -> [a] -> [b]
map forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId [UnitInfo]
directly_shadowed) RevIndex
index UnitInfoMap
pkg_map4
    unusable_shadowed :: UnusableUnits
unusable_shadowed = forall {k} {t} {b} {t} {compid} {srcpkgid} {srcpkgname}
       {modulename} {mod}.
Ord k =>
(t -> b)
-> (t
    -> GenericUnitInfo compid srcpkgid srcpkgname k modulename mod
    -> t)
-> t
-> [GenericUnitInfo compid srcpkgid srcpkgname k modulename mod]
-> Map
     k (GenericUnitInfo compid srcpkgid srcpkgname k modulename mod, b)
mk_unusable [UnitId] -> UnusableUnitReason
ShadowedDependencies UnitInfoMap -> UnitInfo -> [UnitId]
depsAbiMismatch UnitInfoMap
pkg_map5 [UnitInfo]
shadowed

    unusable :: UnusableUnits
unusable = UnusableUnits
directly_ignored forall k a. Ord k => Map k a -> Map k a -> Map k a
`Map.union` UnusableUnits
unusable_ignored
                                forall k a. Ord k => Map k a -> Map k a -> Map k a
`Map.union` UnusableUnits
unusable_broken
                                forall k a. Ord k => Map k a -> Map k a -> Map k a
`Map.union` UnusableUnits
unusable_cyclic
                                forall k a. Ord k => Map k a -> Map k a -> Map k a
`Map.union` UnusableUnits
unusable_shadowed

-- -----------------------------------------------------------------------------
-- When all the command-line options are in, we can process our unit
-- settings and populate the unit state.

mkUnitState
    :: SDocContext            -- ^ SDocContext used to render exception messages
    -> (Int -> SDoc -> IO ()) -- ^ Trace printer
    -> UnitConfig
    -> IO (UnitState,[UnitDatabase UnitId])
mkUnitState :: SDocContext
-> (Int -> SDoc -> IO ())
-> UnitConfig
-> IO (UnitState, [UnitDatabase UnitId])
mkUnitState SDocContext
ctx Int -> SDoc -> IO ()
printer UnitConfig
cfg = do
{-
   Plan.

   There are two main steps for making the package state:

    1. We want to build a single, unified package database based
       on all of the input databases, which upholds the invariant that
       there is only one package per any UnitId and there are no
       dangling dependencies.  We'll do this by merging, and
       then successively filtering out bad dependencies.

       a) Merge all the databases together.
          If an input database defines unit ID that is already in
          the unified database, that package SHADOWS the existing
          package in the current unified database.  Note that
          order is important: packages defined later in the list of
          command line arguments shadow those defined earlier.

       b) Remove all packages with missing dependencies, or
          mutually recursive dependencies.

       b) Remove packages selected by -ignore-package from input database

       c) Remove all packages which depended on packages that are now
          shadowed by an ABI-incompatible package

       d) report (with -v) any packages that were removed by steps 1-3

    2. We want to look at the flags controlling package visibility,
       and build a mapping of what module names are in scope and
       where they live.

       a) on the final, unified database, we apply -trust/-distrust
          flags directly, modifying the database so that the 'trusted'
          field has the correct value.

       b) we use the -package/-hide-package flags to compute a
          visibility map, stating what packages are "exposed" for
          the purposes of computing the module map.
          * if any flag refers to a package which was removed by 1-5, then
            we can give an error message explaining why
          * if -hide-all-packages was not specified, this step also
            hides packages which are superseded by later exposed packages
          * this step is done TWICE if -plugin-package/-hide-all-plugin-packages
            are used

       c) based on the visibility map, we pick wired packages and rewrite
          them to have the expected unitId.

       d) finally, using the visibility map and the package database,
          we build a mapping saying what every in scope module name points to.
-}

  -- if databases have not been provided, read the database flags
  [UnitDatabase UnitId]
raw_dbs <- case UnitConfig -> Maybe [UnitDatabase UnitId]
unitConfigDBCache UnitConfig
cfg of
               Maybe [UnitDatabase UnitId]
Nothing  -> (Int -> SDoc -> IO ()) -> UnitConfig -> IO [UnitDatabase UnitId]
readUnitDatabases Int -> SDoc -> IO ()
printer UnitConfig
cfg
               Just [UnitDatabase UnitId]
dbs -> forall (m :: * -> *) a. Monad m => a -> m a
return [UnitDatabase UnitId]
dbs

  -- distrust all units if the flag is set
  let distrust_all :: UnitDatabase UnitId -> UnitDatabase UnitId
distrust_all UnitDatabase UnitId
db = UnitDatabase UnitId
db { unitDatabaseUnits :: [UnitInfo]
unitDatabaseUnits = [UnitInfo] -> [UnitInfo]
distrustAllUnits (forall unit. UnitDatabase unit -> [GenUnitInfo unit]
unitDatabaseUnits UnitDatabase UnitId
db) }
      dbs :: [UnitDatabase UnitId]
dbs | UnitConfig -> Bool
unitConfigDistrustAll UnitConfig
cfg = forall a b. (a -> b) -> [a] -> [b]
map UnitDatabase UnitId -> UnitDatabase UnitId
distrust_all [UnitDatabase UnitId]
raw_dbs
          | Bool
otherwise                 = [UnitDatabase UnitId]
raw_dbs


  -- This, and the other reverse's that you will see, are due to the fact that
  -- packageFlags, pluginPackageFlags, etc. are all specified in *reverse* order
  -- than they are on the command line.
  let other_flags :: [PackageFlag]
other_flags = forall a. [a] -> [a]
reverse (UnitConfig -> [PackageFlag]
unitConfigFlagsExposed UnitConfig
cfg)
  Int -> SDoc -> IO ()
printer Int
2 forall a b. (a -> b) -> a -> b
$
      String -> SDoc
text String
"package flags" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr [PackageFlag]
other_flags

  -- Merge databases together, without checking validity
  (UnitInfoMap
pkg_map1, UnitPrecedenceMap
prec_map) <- (SDoc -> IO ())
-> [UnitDatabase UnitId] -> IO (UnitInfoMap, UnitPrecedenceMap)
mergeDatabases (Int -> SDoc -> IO ()
printer Int
2) [UnitDatabase UnitId]
dbs

  -- Now that we've merged everything together, prune out unusable
  -- packages.
  let (UnitInfoMap
pkg_map2, UnusableUnits
unusable, [SCC UnitInfo]
sccs) = UnitConfig
-> UnitInfoMap -> (UnitInfoMap, UnusableUnits, [SCC UnitInfo])
validateDatabase UnitConfig
cfg UnitInfoMap
pkg_map1

  (SDoc -> IO ()) -> [SCC UnitInfo] -> IO ()
reportCycles   (Int -> SDoc -> IO ()
printer Int
2) [SCC UnitInfo]
sccs
  (SDoc -> IO ()) -> UnusableUnits -> IO ()
reportUnusable (Int -> SDoc -> IO ()
printer Int
2) UnusableUnits
unusable

  -- Apply trust flags (these flags apply regardless of whether
  -- or not packages are visible or not)
  [UnitInfo]
pkgs1 <- forall a. MaybeErr UnitErr a -> IO a
mayThrowUnitErr
            forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (UnitPrecedenceMap
-> UnusableUnits
-> [UnitInfo]
-> TrustFlag
-> MaybeErr UnitErr [UnitInfo]
applyTrustFlag UnitPrecedenceMap
prec_map UnusableUnits
unusable)
                 (forall k a. Map k a -> [a]
Map.elems UnitInfoMap
pkg_map2) (forall a. [a] -> [a]
reverse (UnitConfig -> [TrustFlag]
unitConfigFlagsTrusted UnitConfig
cfg))
  let prelim_pkg_db :: UnitInfoMap
prelim_pkg_db = [UnitInfo] -> UnitInfoMap
mkUnitInfoMap [UnitInfo]
pkgs1

  --
  -- Calculate the initial set of units from package databases, prior to any package flags.
  --
  -- Conceptually, we select the latest versions of all valid (not unusable) *packages*
  -- (not units). This is empty if we have -hide-all-packages.
  --
  -- Then we create an initial visibility map with default visibilities for all
  -- exposed, definite units which belong to the latest valid packages.
  --
  let preferLater :: UnitInfo -> UnitInfo -> UnitInfo
preferLater UnitInfo
unit UnitInfo
unit' =
        case UnitPrecedenceMap -> UnitInfo -> UnitInfo -> Ordering
compareByPreference UnitPrecedenceMap
prec_map UnitInfo
unit UnitInfo
unit' of
            Ordering
GT -> UnitInfo
unit
            Ordering
_  -> UnitInfo
unit'
      addIfMorePreferable :: UniqDFM FastString UnitInfo
-> UnitInfo -> UniqDFM FastString UnitInfo
addIfMorePreferable UniqDFM FastString UnitInfo
m UnitInfo
unit = forall key elt.
Uniquable key =>
(elt -> elt -> elt)
-> UniqDFM key elt -> key -> elt -> UniqDFM key elt
addToUDFM_C UnitInfo -> UnitInfo -> UnitInfo
preferLater UniqDFM FastString UnitInfo
m (UnitInfo -> FastString
fsPackageName UnitInfo
unit) UnitInfo
unit
      -- This is the set of maximally preferable packages. In fact, it is a set of
      -- most preferable *units* keyed by package name, which act as stand-ins in
      -- for "a package in a database". We use units here because we don't have
      -- "a package in a database" as a type currently.
      mostPreferablePackageReps :: UniqDFM FastString UnitInfo
mostPreferablePackageReps = if UnitConfig -> Bool
unitConfigHideAll UnitConfig
cfg
                    then forall key elt. UniqDFM key elt
emptyUDFM
                    else forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' UniqDFM FastString UnitInfo
-> UnitInfo -> UniqDFM FastString UnitInfo
addIfMorePreferable forall key elt. UniqDFM key elt
emptyUDFM [UnitInfo]
pkgs1
      -- When exposing units, we want to consider all of those in the most preferable
      -- packages. We can implement that by looking for units that are equi-preferable
      -- with the most preferable unit for package. Being equi-preferable means that
      -- they must be in the same database, with the same version, and the same package name.
      --
      -- We must take care to consider all these units and not just the most
      -- preferable one, otherwise we can end up with problems like #16228.
      mostPreferable :: UnitInfo -> Bool
mostPreferable UnitInfo
u =
        case forall key elt.
Uniquable key =>
UniqDFM key elt -> key -> Maybe elt
lookupUDFM UniqDFM FastString UnitInfo
mostPreferablePackageReps (UnitInfo -> FastString
fsPackageName UnitInfo
u) of
          Maybe UnitInfo
Nothing -> Bool
False
          Just UnitInfo
u' -> UnitPrecedenceMap -> UnitInfo -> UnitInfo -> Ordering
compareByPreference UnitPrecedenceMap
prec_map UnitInfo
u UnitInfo
u' forall a. Eq a => a -> a -> Bool
== Ordering
EQ
      vis_map1 :: VisibilityMap
vis_map1 = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\VisibilityMap
vm UnitInfo
p ->
                            -- Note: we NEVER expose indefinite packages by
                            -- default, because it's almost assuredly not
                            -- what you want (no mix-in linking has occurred).
                            if forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Bool
unitIsExposed UnitInfo
p Bool -> Bool -> Bool
&& GenUnit UnitId -> Bool
unitIsDefinite (UnitInfo -> GenUnit UnitId
mkUnit UnitInfo
p) Bool -> Bool -> Bool
&& UnitInfo -> Bool
mostPreferable UnitInfo
p
                               then forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (UnitInfo -> GenUnit UnitId
mkUnit UnitInfo
p)
                                               UnitVisibility {
                                                 uv_expose_all :: Bool
uv_expose_all = Bool
True,
                                                 uv_renamings :: [(ModuleName, ModuleName)]
uv_renamings = [],
                                                 uv_package_name :: First FastString
uv_package_name = forall a. Maybe a -> First a
First (forall a. a -> Maybe a
Just (UnitInfo -> FastString
fsPackageName UnitInfo
p)),
                                                 uv_requirements :: Map ModuleName (Set InstantiatedModule)
uv_requirements = forall k a. Map k a
Map.empty,
                                                 uv_explicit :: Bool
uv_explicit = Bool
False
                                               }
                                               VisibilityMap
vm
                               else VisibilityMap
vm)
                         forall k a. Map k a
Map.empty [UnitInfo]
pkgs1

  --
  -- Compute a visibility map according to the command-line flags (-package,
  -- -hide-package).  This needs to know about the unusable packages, since if a
  -- user tries to enable an unusable package, we should let them know.
  --
  VisibilityMap
vis_map2 <- forall a. MaybeErr UnitErr a -> IO a
mayThrowUnitErr
                forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (UnitPrecedenceMap
-> UnitInfoMap
-> PreloadUnitClosure
-> UnusableUnits
-> Bool
-> [UnitInfo]
-> VisibilityMap
-> PackageFlag
-> MaybeErr UnitErr VisibilityMap
applyPackageFlag UnitPrecedenceMap
prec_map UnitInfoMap
prelim_pkg_db forall a. UniqSet a
emptyUniqSet UnusableUnits
unusable
                        (UnitConfig -> Bool
unitConfigHideAll UnitConfig
cfg) [UnitInfo]
pkgs1)
                            VisibilityMap
vis_map1 [PackageFlag]
other_flags

  --
  -- Sort out which packages are wired in. This has to be done last, since
  -- it modifies the unit ids of wired in packages, but when we process
  -- package arguments we need to key against the old versions.
  --
  ([UnitInfo]
pkgs2, Map UnitId UnitId
wired_map) <- (SDoc -> IO ())
-> UnitPrecedenceMap
-> [UnitInfo]
-> VisibilityMap
-> IO ([UnitInfo], Map UnitId UnitId)
findWiredInUnits (Int -> SDoc -> IO ()
printer Int
2) UnitPrecedenceMap
prec_map [UnitInfo]
pkgs1 VisibilityMap
vis_map2
  let pkg_db :: UnitInfoMap
pkg_db = [UnitInfo] -> UnitInfoMap
mkUnitInfoMap [UnitInfo]
pkgs2

  -- Update the visibility map, so we treat wired packages as visible.
  let vis_map :: VisibilityMap
vis_map = Map UnitId UnitId -> VisibilityMap -> VisibilityMap
updateVisibilityMap Map UnitId UnitId
wired_map VisibilityMap
vis_map2

  let hide_plugin_pkgs :: Bool
hide_plugin_pkgs = UnitConfig -> Bool
unitConfigHideAllPlugins UnitConfig
cfg
  VisibilityMap
plugin_vis_map <-
    case UnitConfig -> [PackageFlag]
unitConfigFlagsPlugins UnitConfig
cfg of
        -- common case; try to share the old vis_map
        [] | Bool -> Bool
not Bool
hide_plugin_pkgs -> forall (m :: * -> *) a. Monad m => a -> m a
return VisibilityMap
vis_map
           | Bool
otherwise -> forall (m :: * -> *) a. Monad m => a -> m a
return forall k a. Map k a
Map.empty
        [PackageFlag]
_ -> do let plugin_vis_map1 :: VisibilityMap
plugin_vis_map1
                        | Bool
hide_plugin_pkgs = forall k a. Map k a
Map.empty
                        -- Use the vis_map PRIOR to wired in,
                        -- because otherwise applyPackageFlag
                        -- won't work.
                        | Bool
otherwise = VisibilityMap
vis_map2
                VisibilityMap
plugin_vis_map2
                    <- forall a. MaybeErr UnitErr a -> IO a
mayThrowUnitErr
                        forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (UnitPrecedenceMap
-> UnitInfoMap
-> PreloadUnitClosure
-> UnusableUnits
-> Bool
-> [UnitInfo]
-> VisibilityMap
-> PackageFlag
-> MaybeErr UnitErr VisibilityMap
applyPackageFlag UnitPrecedenceMap
prec_map UnitInfoMap
prelim_pkg_db forall a. UniqSet a
emptyUniqSet UnusableUnits
unusable
                                Bool
hide_plugin_pkgs [UnitInfo]
pkgs1)
                             VisibilityMap
plugin_vis_map1
                             (forall a. [a] -> [a]
reverse (UnitConfig -> [PackageFlag]
unitConfigFlagsPlugins UnitConfig
cfg))
                -- Updating based on wired in packages is mostly
                -- good hygiene, because it won't matter: no wired in
                -- package has a compiler plugin.
                -- TODO: If a wired in package had a compiler plugin,
                -- and you tried to pick different wired in packages
                -- with the plugin flags and the normal flags... what
                -- would happen?  I don't know!  But this doesn't seem
                -- likely to actually happen.
                forall (m :: * -> *) a. Monad m => a -> m a
return (Map UnitId UnitId -> VisibilityMap -> VisibilityMap
updateVisibilityMap Map UnitId UnitId
wired_map VisibilityMap
plugin_vis_map2)

  let pkgname_map :: UniqFM PackageName IndefUnitId
pkgname_map = forall key elt. Uniquable key => [(key, elt)] -> UniqFM key elt
listToUFM [ (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> srcpkgname
unitPackageName UnitInfo
p, forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> compid
unitInstanceOf UnitInfo
p)
                              | UnitInfo
p <- [UnitInfo]
pkgs2
                              ]
  -- The explicitUnits accurately reflects the set of units we have turned
  -- on; as such, it also is the only way one can come up with requirements.
  -- The requirement context is directly based off of this: we simply
  -- look for nested unit IDs that are directly fed holes: the requirements
  -- of those units are precisely the ones we need to track
  let explicit_pkgs :: [GenUnit UnitId]
explicit_pkgs = forall k a. Map k a -> [k]
Map.keys VisibilityMap
vis_map
      req_ctx :: Map ModuleName [InstantiatedModule]
req_ctx = forall a b k. (a -> b) -> Map k a -> Map k b
Map.map (forall a. Set a -> [a]
Set.toList)
              forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) k a.
(Foldable f, Ord k) =>
(a -> a -> a) -> f (Map k a) -> Map k a
Map.unionsWith forall a. Ord a => Set a -> Set a -> Set a
Set.union (forall a b. (a -> b) -> [a] -> [b]
map UnitVisibility -> Map ModuleName (Set InstantiatedModule)
uv_requirements (forall k a. Map k a -> [a]
Map.elems VisibilityMap
vis_map))


  --
  -- Here we build up a set of the packages mentioned in -package
  -- flags on the command line; these are called the "preload"
  -- packages.  we link these packages in eagerly.  The preload set
  -- should contain at least rts & base, which is why we pretend that
  -- the command line contains -package rts & -package base.
  --
  -- NB: preload IS important even for type-checking, because we
  -- need the correct include path to be set.
  --
  let preload1 :: [GenUnit UnitId]
preload1 = forall k a. Map k a -> [k]
Map.keys (forall a k. (a -> Bool) -> Map k a -> Map k a
Map.filter UnitVisibility -> Bool
uv_explicit VisibilityMap
vis_map)

      -- add default preload units if they can be found in the db
      basicLinkedUnits :: [GenUnit UnitId]
basicLinkedUnits = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall uid. Definite uid -> GenUnit uid
RealUnit forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall unit. unit -> Definite unit
Definite)
                         forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall k a. Ord k => k -> Map k a -> Bool
Map.member UnitInfoMap
pkg_db)
                         forall a b. (a -> b) -> a -> b
$ UnitConfig -> [UnitId]
unitConfigAutoLink UnitConfig
cfg
      preload3 :: [GenUnit UnitId]
preload3 = forall a. Ord a => [a] -> [a]
ordNub forall a b. (a -> b) -> a -> b
$ ([GenUnit UnitId]
basicLinkedUnits forall a. [a] -> [a] -> [a]
++ [GenUnit UnitId]
preload1)

  -- Close the preload packages with their dependencies
  [UnitId]
dep_preload <- forall a. MaybeErr UnitErr a -> IO a
mayThrowUnitErr
                    forall a b. (a -> b) -> a -> b
$ UnitInfoMap
-> [(UnitId, Maybe UnitId)] -> MaybeErr UnitErr [UnitId]
closeUnitDeps UnitInfoMap
pkg_db
                    forall a b. (a -> b) -> a -> b
$ forall a b. [a] -> [b] -> [(a, b)]
zip (forall a b. (a -> b) -> [a] -> [b]
map GenUnit UnitId -> UnitId
toUnitId [GenUnit UnitId]
preload3) (forall a. a -> [a]
repeat forall a. Maybe a
Nothing)

  let mod_map1 :: ModuleNameProvidersMap
mod_map1 = SDocContext
-> UnitConfig
-> UnitInfoMap
-> PreloadUnitClosure
-> VisibilityMap
-> ModuleNameProvidersMap
mkModuleNameProvidersMap SDocContext
ctx UnitConfig
cfg UnitInfoMap
pkg_db forall a. UniqSet a
emptyUniqSet VisibilityMap
vis_map
      mod_map2 :: ModuleNameProvidersMap
mod_map2 = UnusableUnits -> ModuleNameProvidersMap
mkUnusableModuleNameProvidersMap UnusableUnits
unusable
      mod_map :: ModuleNameProvidersMap
mod_map = forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union ModuleNameProvidersMap
mod_map1 ModuleNameProvidersMap
mod_map2

  -- Force the result to avoid leaking input parameters
  let !state :: UnitState
state = UnitState
         { preloadUnits :: [UnitId]
preloadUnits                 = [UnitId]
dep_preload
         , explicitUnits :: [GenUnit UnitId]
explicitUnits                = [GenUnit UnitId]
explicit_pkgs
         , unitInfoMap :: UnitInfoMap
unitInfoMap                  = UnitInfoMap
pkg_db
         , preloadClosure :: PreloadUnitClosure
preloadClosure               = forall a. UniqSet a
emptyUniqSet
         , moduleNameProvidersMap :: ModuleNameProvidersMap
moduleNameProvidersMap       = ModuleNameProvidersMap
mod_map
         , pluginModuleNameProvidersMap :: ModuleNameProvidersMap
pluginModuleNameProvidersMap = SDocContext
-> UnitConfig
-> UnitInfoMap
-> PreloadUnitClosure
-> VisibilityMap
-> ModuleNameProvidersMap
mkModuleNameProvidersMap SDocContext
ctx UnitConfig
cfg UnitInfoMap
pkg_db forall a. UniqSet a
emptyUniqSet VisibilityMap
plugin_vis_map
         , packageNameMap :: UniqFM PackageName IndefUnitId
packageNameMap               = UniqFM PackageName IndefUnitId
pkgname_map
         , wireMap :: Map UnitId UnitId
wireMap                      = Map UnitId UnitId
wired_map
         , unwireMap :: Map UnitId UnitId
unwireMap                    = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [ (UnitId
v,UnitId
k) | (UnitId
k,UnitId
v) <- forall k a. Map k a -> [(k, a)]
Map.toList Map UnitId UnitId
wired_map ]
         , requirementContext :: Map ModuleName [InstantiatedModule]
requirementContext           = Map ModuleName [InstantiatedModule]
req_ctx
         , allowVirtualUnits :: Bool
allowVirtualUnits            = UnitConfig -> Bool
unitConfigAllowVirtual UnitConfig
cfg
         }
  forall (m :: * -> *) a. Monad m => a -> m a
return (UnitState
state, [UnitDatabase UnitId]
raw_dbs)

-- | Given a wired-in 'Unit', "unwire" it into the 'Unit'
-- that it was recorded as in the package database.
unwireUnit :: UnitState -> Unit -> Unit
unwireUnit :: UnitState -> GenUnit UnitId -> GenUnit UnitId
unwireUnit UnitState
state uid :: GenUnit UnitId
uid@(RealUnit (Definite UnitId
def_uid)) =
    forall b a. b -> (a -> b) -> Maybe a -> b
maybe GenUnit UnitId
uid (forall uid. Definite uid -> GenUnit uid
RealUnit forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall unit. unit -> Definite unit
Definite) (forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UnitId
def_uid (UnitState -> Map UnitId UnitId
unwireMap UnitState
state))
unwireUnit UnitState
_ GenUnit UnitId
uid = GenUnit UnitId
uid

-- -----------------------------------------------------------------------------
-- | Makes the mapping from ModuleName to package info

-- Slight irritation: we proceed by leafing through everything
-- in the installed package database, which makes handling indefinite
-- packages a bit bothersome.

mkModuleNameProvidersMap
  :: SDocContext     -- ^ SDocContext used to render exception messages
  -> UnitConfig
  -> UnitInfoMap
  -> PreloadUnitClosure
  -> VisibilityMap
  -> ModuleNameProvidersMap
mkModuleNameProvidersMap :: SDocContext
-> UnitConfig
-> UnitInfoMap
-> PreloadUnitClosure
-> VisibilityMap
-> ModuleNameProvidersMap
mkModuleNameProvidersMap SDocContext
ctx UnitConfig
cfg UnitInfoMap
pkg_map PreloadUnitClosure
closure VisibilityMap
vis_map =
    -- What should we fold on?  Both situations are awkward:
    --
    --    * Folding on the visibility map means that we won't create
    --      entries for packages that aren't mentioned in vis_map
    --      (e.g., hidden packages, causing #14717)
    --
    --    * Folding on pkg_map is awkward because if we have an
    --      Backpack instantiation, we need to possibly add a
    --      package from pkg_map multiple times to the actual
    --      ModuleNameProvidersMap.  Also, we don't really want
    --      definite package instantiations to show up in the
    --      list of possibilities.
    --
    -- So what will we do instead?  We'll extend vis_map with
    -- entries for every definite (for non-Backpack) and
    -- indefinite (for Backpack) package, so that we get the
    -- hidden entries we need.
    forall a k b. (a -> k -> b -> a) -> a -> Map k b -> a
Map.foldlWithKey ModuleNameProvidersMap
-> GenUnit UnitId -> UnitVisibility -> ModuleNameProvidersMap
extend_modmap forall k a. Map k a
emptyMap VisibilityMap
vis_map_extended
 where
  vis_map_extended :: VisibilityMap
vis_map_extended = forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union VisibilityMap
vis_map {- preferred -} VisibilityMap
default_vis

  default_vis :: VisibilityMap
default_vis = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
                  [ (UnitInfo -> GenUnit UnitId
mkUnit UnitInfo
pkg, forall a. Monoid a => a
mempty)
                  | UnitInfo
pkg <- forall k a. Map k a -> [a]
Map.elems UnitInfoMap
pkg_map
                  -- Exclude specific instantiations of an indefinite
                  -- package
                  , forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Bool
unitIsIndefinite UnitInfo
pkg Bool -> Bool -> Bool
|| forall (t :: * -> *) a. Foldable t => t a -> Bool
null (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [(modulename, mod)]
unitInstantiations UnitInfo
pkg)
                  ]

  emptyMap :: Map k a
emptyMap = forall k a. Map k a
Map.empty
  setOrigins :: f a -> b -> f b
setOrigins f a
m b
os = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a b. a -> b -> a
const b
os) f a
m
  extend_modmap :: ModuleNameProvidersMap
-> GenUnit UnitId -> UnitVisibility -> ModuleNameProvidersMap
extend_modmap ModuleNameProvidersMap
modmap GenUnit UnitId
uid
    UnitVisibility { uv_expose_all :: UnitVisibility -> Bool
uv_expose_all = Bool
b, uv_renamings :: UnitVisibility -> [(ModuleName, ModuleName)]
uv_renamings = [(ModuleName, ModuleName)]
rns }
    = forall a k1 k2.
(Monoid a, Ord k1, Ord k2) =>
Map k1 (Map k2 a) -> [(k1, Map k2 a)] -> Map k1 (Map k2 a)
addListTo ModuleNameProvidersMap
modmap [(ModuleName, Map Module ModuleOrigin)]
theBindings
   where
    pkg :: UnitInfo
pkg = GenUnit UnitId -> UnitInfo
unit_lookup GenUnit UnitId
uid

    theBindings :: [(ModuleName, Map Module ModuleOrigin)]
    theBindings :: [(ModuleName, Map Module ModuleOrigin)]
theBindings = Bool
-> [(ModuleName, ModuleName)]
-> [(ModuleName, Map Module ModuleOrigin)]
newBindings Bool
b [(ModuleName, ModuleName)]
rns

    newBindings :: Bool
                -> [(ModuleName, ModuleName)]
                -> [(ModuleName, Map Module ModuleOrigin)]
    newBindings :: Bool
-> [(ModuleName, ModuleName)]
-> [(ModuleName, Map Module ModuleOrigin)]
newBindings Bool
e [(ModuleName, ModuleName)]
rns  = Bool -> [(ModuleName, Map Module ModuleOrigin)]
es Bool
e forall a. [a] -> [a] -> [a]
++ [(ModuleName, Map Module ModuleOrigin)]
hiddens forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map (ModuleName, ModuleName) -> (ModuleName, Map Module ModuleOrigin)
rnBinding [(ModuleName, ModuleName)]
rns

    rnBinding :: (ModuleName, ModuleName)
              -> (ModuleName, Map Module ModuleOrigin)
    rnBinding :: (ModuleName, ModuleName) -> (ModuleName, Map Module ModuleOrigin)
rnBinding (ModuleName
orig, ModuleName
new) = (ModuleName
new, forall {f :: * -> *} {a} {b}. Functor f => f a -> b -> f b
setOrigins Map Module ModuleOrigin
origEntry ModuleOrigin
fromFlag)
     where origEntry :: Map Module ModuleOrigin
origEntry = case forall key elt. Uniquable key => UniqFM key elt -> key -> Maybe elt
lookupUFM UniqFM ModuleName (Map Module ModuleOrigin)
esmap ModuleName
orig of
            Just Map Module ModuleOrigin
r -> Map Module ModuleOrigin
r
            Maybe (Map Module ModuleOrigin)
Nothing -> forall a. GhcException -> a
throwGhcException (String -> GhcException
CmdLineError (SDocContext -> SDoc -> String
renderWithContext SDocContext
ctx
                        (String -> SDoc
text String
"package flag: could not find module name" SDoc -> SDoc -> SDoc
<+>
                            forall a. Outputable a => a -> SDoc
ppr ModuleName
orig SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"in package" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr GenUnit UnitId
pk)))

    es :: Bool -> [(ModuleName, Map Module ModuleOrigin)]
    es :: Bool -> [(ModuleName, Map Module ModuleOrigin)]
es Bool
e = do
     (ModuleName
m, Maybe Module
exposedReexport) <- [(ModuleName, Maybe Module)]
exposed_mods
     let (GenUnit UnitId
pk', ModuleName
m', ModuleOrigin
origin') =
          case Maybe Module
exposedReexport of
           Maybe Module
Nothing -> (GenUnit UnitId
pk, ModuleName
m, Bool -> ModuleOrigin
fromExposedModules Bool
e)
           Just (Module GenUnit UnitId
pk' ModuleName
m') ->
              (GenUnit UnitId
pk', ModuleName
m', Bool -> UnitInfo -> ModuleOrigin
fromReexportedModules Bool
e UnitInfo
pkg)
     forall (m :: * -> *) a. Monad m => a -> m a
return (ModuleName
m, GenUnit UnitId
-> ModuleName -> ModuleOrigin -> Map Module ModuleOrigin
mkModMap GenUnit UnitId
pk' ModuleName
m' ModuleOrigin
origin')

    esmap :: UniqFM ModuleName (Map Module ModuleOrigin)
    esmap :: UniqFM ModuleName (Map Module ModuleOrigin)
esmap = forall key elt. Uniquable key => [(key, elt)] -> UniqFM key elt
listToUFM (Bool -> [(ModuleName, Map Module ModuleOrigin)]
es Bool
False) -- parameter here doesn't matter, orig will
                                 -- be overwritten

    hiddens :: [(ModuleName, Map Module ModuleOrigin)]
hiddens = [(ModuleName
m, GenUnit UnitId
-> ModuleName -> ModuleOrigin -> Map Module ModuleOrigin
mkModMap GenUnit UnitId
pk ModuleName
m ModuleOrigin
ModHidden) | ModuleName
m <- [ModuleName]
hidden_mods]

    pk :: GenUnit UnitId
pk = UnitInfo -> GenUnit UnitId
mkUnit UnitInfo
pkg
    unit_lookup :: GenUnit UnitId -> UnitInfo
unit_lookup GenUnit UnitId
uid = Bool
-> UnitInfoMap
-> PreloadUnitClosure
-> GenUnit UnitId
-> Maybe UnitInfo
lookupUnit' (UnitConfig -> Bool
unitConfigAllowVirtual UnitConfig
cfg) UnitInfoMap
pkg_map PreloadUnitClosure
closure GenUnit UnitId
uid
                        forall a. Maybe a -> a -> a
`orElse` forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"unit_lookup" (forall a. Outputable a => a -> SDoc
ppr GenUnit UnitId
uid)

    exposed_mods :: [(ModuleName, Maybe Module)]
exposed_mods = forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [(modulename, Maybe mod)]
unitExposedModules UnitInfo
pkg
    hidden_mods :: [ModuleName]
hidden_mods  = forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [modulename]
unitHiddenModules UnitInfo
pkg

-- | Make a 'ModuleNameProvidersMap' covering a set of unusable packages.
mkUnusableModuleNameProvidersMap :: UnusableUnits -> ModuleNameProvidersMap
mkUnusableModuleNameProvidersMap :: UnusableUnits -> ModuleNameProvidersMap
mkUnusableModuleNameProvidersMap UnusableUnits
unusables =
    forall a b k. (a -> b -> a) -> a -> Map k b -> a
Map.foldl' ModuleNameProvidersMap
-> (UnitInfo, UnusableUnitReason) -> ModuleNameProvidersMap
extend_modmap forall k a. Map k a
Map.empty UnusableUnits
unusables
 where
    extend_modmap :: ModuleNameProvidersMap
-> (UnitInfo, UnusableUnitReason) -> ModuleNameProvidersMap
extend_modmap ModuleNameProvidersMap
modmap (UnitInfo
pkg, UnusableUnitReason
reason) = forall a k1 k2.
(Monoid a, Ord k1, Ord k2) =>
Map k1 (Map k2 a) -> [(k1, Map k2 a)] -> Map k1 (Map k2 a)
addListTo ModuleNameProvidersMap
modmap [(ModuleName, Map Module ModuleOrigin)]
bindings
      where bindings :: [(ModuleName, Map Module ModuleOrigin)]
            bindings :: [(ModuleName, Map Module ModuleOrigin)]
bindings = [(ModuleName, Map Module ModuleOrigin)]
exposed forall a. [a] -> [a] -> [a]
++ [(ModuleName, Map Module ModuleOrigin)]
hidden

            origin :: ModuleOrigin
origin = UnusableUnitReason -> ModuleOrigin
ModUnusable UnusableUnitReason
reason
            pkg_id :: GenUnit UnitId
pkg_id = UnitInfo -> GenUnit UnitId
mkUnit UnitInfo
pkg

            exposed :: [(ModuleName, Map Module ModuleOrigin)]
exposed = forall a b. (a -> b) -> [a] -> [b]
map (ModuleName, Maybe Module) -> (ModuleName, Map Module ModuleOrigin)
get_exposed [(ModuleName, Maybe Module)]
exposed_mods
            hidden :: [(ModuleName, Map Module ModuleOrigin)]
hidden = [(ModuleName
m, GenUnit UnitId
-> ModuleName -> ModuleOrigin -> Map Module ModuleOrigin
mkModMap GenUnit UnitId
pkg_id ModuleName
m ModuleOrigin
origin) | ModuleName
m <- [ModuleName]
hidden_mods]

            get_exposed :: (ModuleName, Maybe Module) -> (ModuleName, Map Module ModuleOrigin)
get_exposed (ModuleName
mod, Just Module
mod') = (ModuleName
mod, forall k a. k -> a -> Map k a
Map.singleton Module
mod' ModuleOrigin
origin)
            get_exposed (ModuleName
mod, Maybe Module
_)         = (ModuleName
mod, GenUnit UnitId
-> ModuleName -> ModuleOrigin -> Map Module ModuleOrigin
mkModMap GenUnit UnitId
pkg_id ModuleName
mod ModuleOrigin
origin)

            exposed_mods :: [(ModuleName, Maybe Module)]
exposed_mods = forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [(modulename, Maybe mod)]
unitExposedModules UnitInfo
pkg
            hidden_mods :: [ModuleName]
hidden_mods  = forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [modulename]
unitHiddenModules UnitInfo
pkg

-- | Add a list of key/value pairs to a nested map.
--
-- The outer map is processed with 'Data.Map.Strict' to prevent memory leaks
-- when reloading modules in GHCi (see #4029). This ensures that each
-- value is forced before installing into the map.
addListTo :: (Monoid a, Ord k1, Ord k2)
          => Map k1 (Map k2 a)
          -> [(k1, Map k2 a)]
          -> Map k1 (Map k2 a)
addListTo :: forall a k1 k2.
(Monoid a, Ord k1, Ord k2) =>
Map k1 (Map k2 a) -> [(k1, Map k2 a)] -> Map k1 (Map k2 a)
addListTo = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' forall {k} {k} {a}.
(Ord k, Ord k, Monoid a) =>
Map k (Map k a) -> (k, Map k a) -> Map k (Map k a)
merge
  where merge :: Map k (Map k a) -> (k, Map k a) -> Map k (Map k a)
merge Map k (Map k a)
m (k
k, Map k a
v) = forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
MapStrict.insertWith (forall k a. Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
Map.unionWith forall a. Monoid a => a -> a -> a
mappend) k
k Map k a
v Map k (Map k a)
m

-- | Create a singleton module mapping
mkModMap :: Unit -> ModuleName -> ModuleOrigin -> Map Module ModuleOrigin
mkModMap :: GenUnit UnitId
-> ModuleName -> ModuleOrigin -> Map Module ModuleOrigin
mkModMap GenUnit UnitId
pkg ModuleName
mod = forall k a. k -> a -> Map k a
Map.singleton (forall unit. unit -> ModuleName -> GenModule unit
mkModule GenUnit UnitId
pkg ModuleName
mod)


-- -----------------------------------------------------------------------------
-- Package Utils

-- | Takes a 'ModuleName', and if the module is in any package returns
-- list of modules which take that name.
lookupModuleInAllUnits :: UnitState
                          -> ModuleName
                          -> [(Module, UnitInfo)]
lookupModuleInAllUnits :: UnitState -> ModuleName -> [(Module, UnitInfo)]
lookupModuleInAllUnits UnitState
pkgs ModuleName
m
  = case UnitState -> ModuleName -> Maybe FastString -> LookupResult
lookupModuleWithSuggestions UnitState
pkgs ModuleName
m forall a. Maybe a
Nothing of
      LookupFound Module
a (UnitInfo, ModuleOrigin)
b -> [(Module
a,forall a b. (a, b) -> a
fst (UnitInfo, ModuleOrigin)
b)]
      LookupMultiple [(Module, ModuleOrigin)]
rs -> forall a b. (a -> b) -> [a] -> [b]
map (Module, ModuleOrigin) -> (Module, UnitInfo)
f [(Module, ModuleOrigin)]
rs
        where f :: (Module, ModuleOrigin) -> (Module, UnitInfo)
f (Module
m,ModuleOrigin
_) = (Module
m, forall a. HasCallStack => String -> Maybe a -> a
expectJust String
"lookupModule" (UnitState -> GenUnit UnitId -> Maybe UnitInfo
lookupUnit UnitState
pkgs
                                                         (forall unit. GenModule unit -> unit
moduleUnit Module
m)))
      LookupResult
_ -> []

-- | The result of performing a lookup
data LookupResult =
    -- | Found the module uniquely, nothing else to do
    LookupFound Module (UnitInfo, ModuleOrigin)
    -- | Multiple modules with the same name in scope
  | LookupMultiple [(Module, ModuleOrigin)]
    -- | No modules found, but there were some hidden ones with
    -- an exact name match.  First is due to package hidden, second
    -- is due to module being hidden
  | LookupHidden [(Module, ModuleOrigin)] [(Module, ModuleOrigin)]
    -- | No modules found, but there were some unusable ones with
    -- an exact name match
  | LookupUnusable [(Module, ModuleOrigin)]
    -- | Nothing found, here are some suggested different names
  | LookupNotFound [ModuleSuggestion] -- suggestions

data ModuleSuggestion = SuggestVisible ModuleName Module ModuleOrigin
                      | SuggestHidden ModuleName Module ModuleOrigin

lookupModuleWithSuggestions :: UnitState
                            -> ModuleName
                            -> Maybe FastString
                            -> LookupResult
lookupModuleWithSuggestions :: UnitState -> ModuleName -> Maybe FastString -> LookupResult
lookupModuleWithSuggestions UnitState
pkgs
  = UnitState
-> ModuleNameProvidersMap
-> ModuleName
-> Maybe FastString
-> LookupResult
lookupModuleWithSuggestions' UnitState
pkgs (UnitState -> ModuleNameProvidersMap
moduleNameProvidersMap UnitState
pkgs)

-- | The package which the module **appears** to come from, this could be
-- the one which reexports the module from it's original package. This function
-- is currently only used for -Wunused-packages
lookupModulePackage :: UnitState -> ModuleName -> Maybe FastString -> Maybe [UnitInfo]
lookupModulePackage :: UnitState -> ModuleName -> Maybe FastString -> Maybe [UnitInfo]
lookupModulePackage UnitState
pkgs ModuleName
mn Maybe FastString
mfs =
    case UnitState
-> ModuleNameProvidersMap
-> ModuleName
-> Maybe FastString
-> LookupResult
lookupModuleWithSuggestions' UnitState
pkgs (UnitState -> ModuleNameProvidersMap
moduleNameProvidersMap UnitState
pkgs) ModuleName
mn Maybe FastString
mfs of
      LookupFound Module
_ (UnitInfo
orig_unit, ModuleOrigin
origin) ->
        case ModuleOrigin
origin of
          ModOrigin {Maybe Bool
fromOrigUnit :: Maybe Bool
fromOrigUnit :: ModuleOrigin -> Maybe Bool
fromOrigUnit, [UnitInfo]
fromExposedReexport :: [UnitInfo]
fromExposedReexport :: ModuleOrigin -> [UnitInfo]
fromExposedReexport} ->
            case Maybe Bool
fromOrigUnit of
              -- Just True means, the import is available from its original location
              Just Bool
True ->
                forall (f :: * -> *) a. Applicative f => a -> f a
pure [UnitInfo
orig_unit]
              -- Otherwise, it must be available from a reexport
              Maybe Bool
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure [UnitInfo]
fromExposedReexport

          ModuleOrigin
_ -> forall a. Maybe a
Nothing

      LookupResult
_ -> forall a. Maybe a
Nothing

lookupPluginModuleWithSuggestions :: UnitState
                                  -> ModuleName
                                  -> Maybe FastString
                                  -> LookupResult
lookupPluginModuleWithSuggestions :: UnitState -> ModuleName -> Maybe FastString -> LookupResult
lookupPluginModuleWithSuggestions UnitState
pkgs
  = UnitState
-> ModuleNameProvidersMap
-> ModuleName
-> Maybe FastString
-> LookupResult
lookupModuleWithSuggestions' UnitState
pkgs (UnitState -> ModuleNameProvidersMap
pluginModuleNameProvidersMap UnitState
pkgs)

lookupModuleWithSuggestions' :: UnitState
                            -> ModuleNameProvidersMap
                            -> ModuleName
                            -> Maybe FastString
                            -> LookupResult
lookupModuleWithSuggestions' :: UnitState
-> ModuleNameProvidersMap
-> ModuleName
-> Maybe FastString
-> LookupResult
lookupModuleWithSuggestions' UnitState
pkgs ModuleNameProvidersMap
mod_map ModuleName
m Maybe FastString
mb_pn
  = case forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup ModuleName
m ModuleNameProvidersMap
mod_map of
        Maybe (Map Module ModuleOrigin)
Nothing -> [ModuleSuggestion] -> LookupResult
LookupNotFound [ModuleSuggestion]
suggestions
        Just Map Module ModuleOrigin
xs ->
          case forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' ([(Module, ModuleOrigin)], [(Module, ModuleOrigin)],
 [(Module, ModuleOrigin)], [(Module, ModuleOrigin)])
-> (Module, ModuleOrigin)
-> ([(Module, ModuleOrigin)], [(Module, ModuleOrigin)],
    [(Module, ModuleOrigin)], [(Module, ModuleOrigin)])
classify ([],[],[], []) (forall k a. Map k a -> [(k, a)]
Map.toList Map Module ModuleOrigin
xs) of
            ([], [], [], []) -> [ModuleSuggestion] -> LookupResult
LookupNotFound [ModuleSuggestion]
suggestions
            ([(Module, ModuleOrigin)]
_, [(Module, ModuleOrigin)]
_, [(Module, ModuleOrigin)]
_, [(Module
m, ModuleOrigin
o)])             -> Module -> (UnitInfo, ModuleOrigin) -> LookupResult
LookupFound Module
m (Module -> UnitInfo
mod_unit Module
m, ModuleOrigin
o)
            ([(Module, ModuleOrigin)]
_, [(Module, ModuleOrigin)]
_, [(Module, ModuleOrigin)]
_, exposed :: [(Module, ModuleOrigin)]
exposed@((Module, ModuleOrigin)
_:[(Module, ModuleOrigin)]
_))        -> [(Module, ModuleOrigin)] -> LookupResult
LookupMultiple [(Module, ModuleOrigin)]
exposed
            ([], [], unusable :: [(Module, ModuleOrigin)]
unusable@((Module, ModuleOrigin)
_:[(Module, ModuleOrigin)]
_), [])    -> [(Module, ModuleOrigin)] -> LookupResult
LookupUnusable [(Module, ModuleOrigin)]
unusable
            ([(Module, ModuleOrigin)]
hidden_pkg, [(Module, ModuleOrigin)]
hidden_mod, [(Module, ModuleOrigin)]
_, []) ->
              [(Module, ModuleOrigin)]
-> [(Module, ModuleOrigin)] -> LookupResult
LookupHidden [(Module, ModuleOrigin)]
hidden_pkg [(Module, ModuleOrigin)]
hidden_mod
  where
    classify :: ([(Module, ModuleOrigin)], [(Module, ModuleOrigin)],
 [(Module, ModuleOrigin)], [(Module, ModuleOrigin)])
-> (Module, ModuleOrigin)
-> ([(Module, ModuleOrigin)], [(Module, ModuleOrigin)],
    [(Module, ModuleOrigin)], [(Module, ModuleOrigin)])
classify ([(Module, ModuleOrigin)]
hidden_pkg, [(Module, ModuleOrigin)]
hidden_mod, [(Module, ModuleOrigin)]
unusable, [(Module, ModuleOrigin)]
exposed) (Module
m, ModuleOrigin
origin0) =
      let origin :: ModuleOrigin
origin = Maybe FastString -> UnitInfo -> ModuleOrigin -> ModuleOrigin
filterOrigin Maybe FastString
mb_pn (Module -> UnitInfo
mod_unit Module
m) ModuleOrigin
origin0
          x :: (Module, ModuleOrigin)
x = (Module
m, ModuleOrigin
origin)
      in case ModuleOrigin
origin of
          ModuleOrigin
ModHidden
            -> ([(Module, ModuleOrigin)]
hidden_pkg, (Module, ModuleOrigin)
xforall a. a -> [a] -> [a]
:[(Module, ModuleOrigin)]
hidden_mod, [(Module, ModuleOrigin)]
unusable, [(Module, ModuleOrigin)]
exposed)
          ModUnusable UnusableUnitReason
_
            -> ([(Module, ModuleOrigin)]
hidden_pkg, [(Module, ModuleOrigin)]
hidden_mod, (Module, ModuleOrigin)
xforall a. a -> [a] -> [a]
:[(Module, ModuleOrigin)]
unusable, [(Module, ModuleOrigin)]
exposed)
          ModuleOrigin
_ | ModuleOrigin -> Bool
originEmpty ModuleOrigin
origin
            -> ([(Module, ModuleOrigin)]
hidden_pkg,   [(Module, ModuleOrigin)]
hidden_mod, [(Module, ModuleOrigin)]
unusable, [(Module, ModuleOrigin)]
exposed)
            | ModuleOrigin -> Bool
originVisible ModuleOrigin
origin
            -> ([(Module, ModuleOrigin)]
hidden_pkg, [(Module, ModuleOrigin)]
hidden_mod, [(Module, ModuleOrigin)]
unusable, (Module, ModuleOrigin)
xforall a. a -> [a] -> [a]
:[(Module, ModuleOrigin)]
exposed)
            | Bool
otherwise
            -> ((Module, ModuleOrigin)
xforall a. a -> [a] -> [a]
:[(Module, ModuleOrigin)]
hidden_pkg, [(Module, ModuleOrigin)]
hidden_mod, [(Module, ModuleOrigin)]
unusable, [(Module, ModuleOrigin)]
exposed)

    unit_lookup :: GenUnit UnitId -> UnitInfo
unit_lookup GenUnit UnitId
p = UnitState -> GenUnit UnitId -> Maybe UnitInfo
lookupUnit UnitState
pkgs GenUnit UnitId
p forall a. Maybe a -> a -> a
`orElse` forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"lookupModuleWithSuggestions" (forall a. Outputable a => a -> SDoc
ppr GenUnit UnitId
p SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr ModuleName
m)
    mod_unit :: Module -> UnitInfo
mod_unit = GenUnit UnitId -> UnitInfo
unit_lookup forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall unit. GenModule unit -> unit
moduleUnit

    -- Filters out origins which are not associated with the given package
    -- qualifier.  No-op if there is no package qualifier.  Test if this
    -- excluded all origins with 'originEmpty'.
    filterOrigin :: Maybe FastString
                 -> UnitInfo
                 -> ModuleOrigin
                 -> ModuleOrigin
    filterOrigin :: Maybe FastString -> UnitInfo -> ModuleOrigin -> ModuleOrigin
filterOrigin Maybe FastString
Nothing UnitInfo
_ ModuleOrigin
o = ModuleOrigin
o
    filterOrigin (Just FastString
pn) UnitInfo
pkg ModuleOrigin
o =
      case ModuleOrigin
o of
          ModuleOrigin
ModHidden -> if UnitInfo -> Bool
go UnitInfo
pkg then ModuleOrigin
ModHidden else forall a. Monoid a => a
mempty
          (ModUnusable UnusableUnitReason
_) -> if UnitInfo -> Bool
go UnitInfo
pkg then ModuleOrigin
o else forall a. Monoid a => a
mempty
          ModOrigin { fromOrigUnit :: ModuleOrigin -> Maybe Bool
fromOrigUnit = Maybe Bool
e, fromExposedReexport :: ModuleOrigin -> [UnitInfo]
fromExposedReexport = [UnitInfo]
res,
                      fromHiddenReexport :: ModuleOrigin -> [UnitInfo]
fromHiddenReexport = [UnitInfo]
rhs }
            -> ModOrigin {
                  fromOrigUnit :: Maybe Bool
fromOrigUnit = if UnitInfo -> Bool
go UnitInfo
pkg then Maybe Bool
e else forall a. Maybe a
Nothing
                , fromExposedReexport :: [UnitInfo]
fromExposedReexport = forall a. (a -> Bool) -> [a] -> [a]
filter UnitInfo -> Bool
go [UnitInfo]
res
                , fromHiddenReexport :: [UnitInfo]
fromHiddenReexport = forall a. (a -> Bool) -> [a] -> [a]
filter UnitInfo -> Bool
go [UnitInfo]
rhs
                , fromPackageFlag :: Bool
fromPackageFlag = Bool
False -- always excluded
                }
      where go :: UnitInfo -> Bool
go UnitInfo
pkg = FastString
pn forall a. Eq a => a -> a -> Bool
== UnitInfo -> FastString
fsPackageName UnitInfo
pkg

    suggestions :: [ModuleSuggestion]
suggestions = forall a. String -> [(String, a)] -> [a]
fuzzyLookup (ModuleName -> String
moduleNameString ModuleName
m) [(String, ModuleSuggestion)]
all_mods

    all_mods :: [(String, ModuleSuggestion)]     -- All modules
    all_mods :: [(String, ModuleSuggestion)]
all_mods = forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (forall a t. Ord a => (t -> a) -> t -> t -> Ordering
comparing forall a b. (a, b) -> a
fst) forall a b. (a -> b) -> a -> b
$
        [ (ModuleName -> String
moduleNameString ModuleName
m, ModuleSuggestion
suggestion)
        | (ModuleName
m, Map Module ModuleOrigin
e) <- forall k a. Map k a -> [(k, a)]
Map.toList (UnitState -> ModuleNameProvidersMap
moduleNameProvidersMap UnitState
pkgs)
        , ModuleSuggestion
suggestion <- forall a b. (a -> b) -> [a] -> [b]
map (ModuleName -> (Module, ModuleOrigin) -> ModuleSuggestion
getSuggestion ModuleName
m) (forall k a. Map k a -> [(k, a)]
Map.toList Map Module ModuleOrigin
e)
        ]
    getSuggestion :: ModuleName -> (Module, ModuleOrigin) -> ModuleSuggestion
getSuggestion ModuleName
name (Module
mod, ModuleOrigin
origin) =
        (if ModuleOrigin -> Bool
originVisible ModuleOrigin
origin then ModuleName -> Module -> ModuleOrigin -> ModuleSuggestion
SuggestVisible else ModuleName -> Module -> ModuleOrigin -> ModuleSuggestion
SuggestHidden)
            ModuleName
name Module
mod ModuleOrigin
origin

listVisibleModuleNames :: UnitState -> [ModuleName]
listVisibleModuleNames :: UnitState -> [ModuleName]
listVisibleModuleNames UnitState
state =
    forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst (forall a. (a -> Bool) -> [a] -> [a]
filter forall {a} {k}. (a, Map k ModuleOrigin) -> Bool
visible (forall k a. Map k a -> [(k, a)]
Map.toList (UnitState -> ModuleNameProvidersMap
moduleNameProvidersMap UnitState
state)))
  where visible :: (a, Map k ModuleOrigin) -> Bool
visible (a
_, Map k ModuleOrigin
ms) = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ModuleOrigin -> Bool
originVisible (forall k a. Map k a -> [a]
Map.elems Map k ModuleOrigin
ms)

-- | Takes a list of UnitIds (and their "parent" dependency, used for error
-- messages), and returns the list with dependencies included, in reverse
-- dependency order (a units appears before those it depends on).
closeUnitDeps :: UnitInfoMap -> [(UnitId,Maybe UnitId)] -> MaybeErr UnitErr [UnitId]
closeUnitDeps :: UnitInfoMap
-> [(UnitId, Maybe UnitId)] -> MaybeErr UnitErr [UnitId]
closeUnitDeps UnitInfoMap
pkg_map [(UnitId, Maybe UnitId)]
ps = UnitInfoMap
-> [UnitId]
-> [(UnitId, Maybe UnitId)]
-> MaybeErr UnitErr [UnitId]
closeUnitDeps' UnitInfoMap
pkg_map [] [(UnitId, Maybe UnitId)]
ps

-- | Similar to closeUnitDeps but takes a list of already loaded units as an
-- additional argument.
closeUnitDeps' :: UnitInfoMap -> [UnitId] -> [(UnitId,Maybe UnitId)] -> MaybeErr UnitErr [UnitId]
closeUnitDeps' :: UnitInfoMap
-> [UnitId]
-> [(UnitId, Maybe UnitId)]
-> MaybeErr UnitErr [UnitId]
closeUnitDeps' UnitInfoMap
pkg_map [UnitId]
current_ids [(UnitId, Maybe UnitId)]
ps = forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (UnitInfoMap
-> [UnitId] -> (UnitId, Maybe UnitId) -> MaybeErr UnitErr [UnitId]
add_unit UnitInfoMap
pkg_map) [UnitId]
current_ids [(UnitId, Maybe UnitId)]
ps

-- | Add a UnitId and those it depends on (recursively) to the given list of
-- UnitIds if they are not already in it. Return a list in reverse dependency
-- order (a unit appears before those it depends on).
--
-- The UnitId is looked up in the given UnitInfoMap (to find its dependencies).
-- It it's not found, the optional parent unit is used to return a more precise
-- error message ("dependency of <PARENT>").
add_unit :: UnitInfoMap
            -> [UnitId]
            -> (UnitId,Maybe UnitId)
            -> MaybeErr UnitErr [UnitId]
add_unit :: UnitInfoMap
-> [UnitId] -> (UnitId, Maybe UnitId) -> MaybeErr UnitErr [UnitId]
add_unit UnitInfoMap
pkg_map [UnitId]
ps (UnitId
p, Maybe UnitId
mb_parent)
  | UnitId
p forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [UnitId]
ps = forall (m :: * -> *) a. Monad m => a -> m a
return [UnitId]
ps     -- Check if we've already added this unit
  | Bool
otherwise   = case UnitInfoMap -> UnitId -> Maybe UnitInfo
lookupUnitId' UnitInfoMap
pkg_map UnitId
p of
      Maybe UnitInfo
Nothing   -> forall err val. err -> MaybeErr err val
Failed (UnitId -> Maybe UnitId -> UnitErr
CloseUnitErr UnitId
p Maybe UnitId
mb_parent)
      Just UnitInfo
info -> do
         -- Add the unit's dependents also
         [UnitId]
ps' <- forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM [UnitId] -> UnitId -> MaybeErr UnitErr [UnitId]
add_unit_key [UnitId]
ps (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> [uid]
unitDepends UnitInfo
info)
         forall (m :: * -> *) a. Monad m => a -> m a
return (UnitId
p forall a. a -> [a] -> [a]
: [UnitId]
ps')
        where
          add_unit_key :: [UnitId] -> UnitId -> MaybeErr UnitErr [UnitId]
add_unit_key [UnitId]
ps UnitId
key
            = UnitInfoMap
-> [UnitId] -> (UnitId, Maybe UnitId) -> MaybeErr UnitErr [UnitId]
add_unit UnitInfoMap
pkg_map [UnitId]
ps (UnitId
key, forall a. a -> Maybe a
Just UnitId
p)

data UnitErr
  = CloseUnitErr !UnitId !(Maybe UnitId)
  | PackageFlagErr !PackageFlag ![(UnitInfo,UnusableUnitReason)]
  | TrustFlagErr   !TrustFlag   ![(UnitInfo,UnusableUnitReason)]

mayThrowUnitErr :: MaybeErr UnitErr a -> IO a
mayThrowUnitErr :: forall a. MaybeErr UnitErr a -> IO a
mayThrowUnitErr = \case
    Failed UnitErr
e    -> forall a. GhcException -> IO a
throwGhcExceptionIO
                    forall a b. (a -> b) -> a -> b
$ String -> GhcException
CmdLineError
                    forall a b. (a -> b) -> a -> b
$ SDocContext -> SDoc -> String
renderWithContext SDocContext
defaultSDocContext
                    forall a b. (a -> b) -> a -> b
$ PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
defaultUserStyle
                    forall a b. (a -> b) -> a -> b
$ forall a. Outputable a => a -> SDoc
ppr UnitErr
e
    Succeeded a
a -> forall (m :: * -> *) a. Monad m => a -> m a
return a
a

instance Outputable UnitErr where
    ppr :: UnitErr -> SDoc
ppr = \case
        CloseUnitErr UnitId
p Maybe UnitId
mb_parent
            -> (FastString -> SDoc
ftext (String -> FastString
fsLit String
"unknown unit:") SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr UnitId
p)
               SDoc -> SDoc -> SDoc
<> case Maybe UnitId
mb_parent of
                     Maybe UnitId
Nothing     -> SDoc
Outputable.empty
                     Just UnitId
parent -> SDoc
space SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
parens (String -> SDoc
text String
"dependency of"
                                              SDoc -> SDoc -> SDoc
<+> FastString -> SDoc
ftext (UnitId -> FastString
unitIdFS UnitId
parent))
        PackageFlagErr PackageFlag
flag [(UnitInfo, UnusableUnitReason)]
reasons
            -> forall {a} {compid} {srcpkgid} {srcpkgname} {modulename} {mod}.
Outputable a =>
SDoc
-> [(GenericUnitInfo compid srcpkgid srcpkgname a modulename mod,
     UnusableUnitReason)]
-> SDoc
flag_err (PackageFlag -> SDoc
pprFlag PackageFlag
flag) [(UnitInfo, UnusableUnitReason)]
reasons

        TrustFlagErr TrustFlag
flag [(UnitInfo, UnusableUnitReason)]
reasons
            -> forall {a} {compid} {srcpkgid} {srcpkgname} {modulename} {mod}.
Outputable a =>
SDoc
-> [(GenericUnitInfo compid srcpkgid srcpkgname a modulename mod,
     UnusableUnitReason)]
-> SDoc
flag_err (TrustFlag -> SDoc
pprTrustFlag TrustFlag
flag) [(UnitInfo, UnusableUnitReason)]
reasons
      where
        flag_err :: SDoc
-> [(GenericUnitInfo compid srcpkgid srcpkgname a modulename mod,
     UnusableUnitReason)]
-> SDoc
flag_err SDoc
flag_doc [(GenericUnitInfo compid srcpkgid srcpkgname a modulename mod,
  UnusableUnitReason)]
reasons =
            String -> SDoc
text String
"cannot satisfy "
            SDoc -> SDoc -> SDoc
<> SDoc
flag_doc
            SDoc -> SDoc -> SDoc
<> (if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(GenericUnitInfo compid srcpkgid srcpkgname a modulename mod,
  UnusableUnitReason)]
reasons then SDoc
Outputable.empty else String -> SDoc
text String
": ")
            SDoc -> SDoc -> SDoc
$$ Int -> SDoc -> SDoc
nest Int
4 ([SDoc] -> SDoc
vcat (forall a b. (a -> b) -> [a] -> [b]
map forall {a} {compid} {srcpkgid} {srcpkgname} {modulename} {mod}.
Outputable a =>
(GenericUnitInfo compid srcpkgid srcpkgname a modulename mod,
 UnusableUnitReason)
-> SDoc
ppr_reason [(GenericUnitInfo compid srcpkgid srcpkgname a modulename mod,
  UnusableUnitReason)]
reasons) SDoc -> SDoc -> SDoc
$$
                      String -> SDoc
text String
"(use -v for more information)")

        ppr_reason :: (GenericUnitInfo compid srcpkgid srcpkgname a modulename mod,
 UnusableUnitReason)
-> SDoc
ppr_reason (GenericUnitInfo compid srcpkgid srcpkgname a modulename mod
p, UnusableUnitReason
reason) =
            SDoc -> UnusableUnitReason -> SDoc
pprReason (forall a. Outputable a => a -> SDoc
ppr (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId GenericUnitInfo compid srcpkgid srcpkgname a modulename mod
p) SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"is") UnusableUnitReason
reason

-- | Return this list of requirement interfaces that need to be merged
-- to form @mod_name@, or @[]@ if this is not a requirement.
requirementMerges :: UnitState -> ModuleName -> [InstantiatedModule]
requirementMerges :: UnitState -> ModuleName -> [InstantiatedModule]
requirementMerges UnitState
pkgstate ModuleName
mod_name =
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall {unit}.
GenModule (GenInstantiatedUnit unit)
-> GenModule (GenInstantiatedUnit unit)
fixupModule forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a -> a
fromMaybe [] (forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup ModuleName
mod_name (UnitState -> Map ModuleName [InstantiatedModule]
requirementContext UnitState
pkgstate))
    where
      -- update IndefUnitId ppr info as they may have changed since the
      -- time the IndefUnitId was created
      fixupModule :: GenModule (GenInstantiatedUnit unit)
-> GenModule (GenInstantiatedUnit unit)
fixupModule (Module GenInstantiatedUnit unit
iud ModuleName
name) = forall unit. unit -> ModuleName -> GenModule unit
Module GenInstantiatedUnit unit
iud' ModuleName
name
         where
            iud' :: GenInstantiatedUnit unit
iud' = GenInstantiatedUnit unit
iud { instUnitInstanceOf :: Indefinite unit
instUnitInstanceOf = Indefinite unit
cid' }
            cid' :: Indefinite unit
cid' = forall unit. GenInstantiatedUnit unit -> Indefinite unit
instUnitInstanceOf GenInstantiatedUnit unit
iud

-- -----------------------------------------------------------------------------

-- | Pretty-print a UnitId for the user.
--
-- Cabal packages may contain several components (programs, libraries, etc.).
-- As far as GHC is concerned, installed package components ("units") are
-- identified by an opaque IndefUnitId string provided by Cabal. As the string
-- contains a hash, we don't want to display it to users so GHC queries the
-- database to retrieve some infos about the original source package (name,
-- version, component name).
--
-- Instead we want to display: packagename-version[:componentname]
--
-- Component name is only displayed if it isn't the default library
--
-- To do this we need to query a unit database.
pprUnitIdForUser :: UnitState -> UnitId -> SDoc
pprUnitIdForUser :: UnitState -> UnitId -> SDoc
pprUnitIdForUser UnitState
state uid :: UnitId
uid@(UnitId FastString
fs) =
   case UnitState -> UnitId -> Maybe UnitPprInfo
lookupUnitPprInfo UnitState
state UnitId
uid of
      Maybe UnitPprInfo
Nothing -> FastString -> SDoc
ftext FastString
fs -- we didn't find the unit at all
      Just UnitPprInfo
i  -> forall a. Outputable a => a -> SDoc
ppr UnitPprInfo
i

pprUnitInfoForUser :: UnitInfo -> SDoc
pprUnitInfoForUser :: UnitInfo -> SDoc
pprUnitInfoForUser UnitInfo
info = forall a. Outputable a => a -> SDoc
ppr (forall u. (u -> FastString) -> GenUnitInfo u -> UnitPprInfo
mkUnitPprInfo UnitId -> FastString
unitIdFS UnitInfo
info)

lookupUnitPprInfo :: UnitState -> UnitId -> Maybe UnitPprInfo
lookupUnitPprInfo :: UnitState -> UnitId -> Maybe UnitPprInfo
lookupUnitPprInfo UnitState
state UnitId
uid = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall u. (u -> FastString) -> GenUnitInfo u -> UnitPprInfo
mkUnitPprInfo UnitId -> FastString
unitIdFS) (UnitState -> UnitId -> Maybe UnitInfo
lookupUnitId UnitState
state UnitId
uid)

-- -----------------------------------------------------------------------------
-- Displaying packages

-- | Show (very verbose) package info
pprUnits :: UnitState -> SDoc
pprUnits :: UnitState -> SDoc
pprUnits = (UnitInfo -> SDoc) -> UnitState -> SDoc
pprUnitsWith UnitInfo -> SDoc
pprUnitInfo

pprUnitsWith :: (UnitInfo -> SDoc) -> UnitState -> SDoc
pprUnitsWith :: (UnitInfo -> SDoc) -> UnitState -> SDoc
pprUnitsWith UnitInfo -> SDoc
pprIPI UnitState
pkgstate =
    [SDoc] -> SDoc
vcat (forall a. a -> [a] -> [a]
intersperse (String -> SDoc
text String
"---") (forall a b. (a -> b) -> [a] -> [b]
map UnitInfo -> SDoc
pprIPI (UnitState -> [UnitInfo]
listUnitInfo UnitState
pkgstate)))

-- | Show simplified unit info.
--
-- The idea is to only print package id, and any information that might
-- be different from the package databases (exposure, trust)
pprUnitsSimple :: UnitState -> SDoc
pprUnitsSimple :: UnitState -> SDoc
pprUnitsSimple = (UnitInfo -> SDoc) -> UnitState -> SDoc
pprUnitsWith forall {compid} {srcpkgid} {srcpkgname} {modulename} {mod}.
GenericUnitInfo compid srcpkgid srcpkgname UnitId modulename mod
-> SDoc
pprIPI
    where pprIPI :: GenericUnitInfo compid srcpkgid srcpkgname UnitId modulename mod
-> SDoc
pprIPI GenericUnitInfo compid srcpkgid srcpkgname UnitId modulename mod
ipi = let i :: FastString
i = UnitId -> FastString
unitIdFS (forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId GenericUnitInfo compid srcpkgid srcpkgname UnitId modulename mod
ipi)
                           e :: SDoc
e = if forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Bool
unitIsExposed GenericUnitInfo compid srcpkgid srcpkgname UnitId modulename mod
ipi then String -> SDoc
text String
"E" else String -> SDoc
text String
" "
                           t :: SDoc
t = if forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> Bool
unitIsTrusted GenericUnitInfo compid srcpkgid srcpkgname UnitId modulename mod
ipi then String -> SDoc
text String
"T" else String -> SDoc
text String
" "
                       in SDoc
e SDoc -> SDoc -> SDoc
<> SDoc
t SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"  " SDoc -> SDoc -> SDoc
<> FastString -> SDoc
ftext FastString
i

-- | Show the mapping of modules to where they come from.
pprModuleMap :: ModuleNameProvidersMap -> SDoc
pprModuleMap :: ModuleNameProvidersMap -> SDoc
pprModuleMap ModuleNameProvidersMap
mod_map =
  [SDoc] -> SDoc
vcat (forall a b. (a -> b) -> [a] -> [b]
map forall {a}. Outputable a => (ModuleName, Map Module a) -> SDoc
pprLine (forall k a. Map k a -> [(k, a)]
Map.toList ModuleNameProvidersMap
mod_map))
    where
      pprLine :: (ModuleName, Map Module a) -> SDoc
pprLine (ModuleName
m,Map Module a
e) = forall a. Outputable a => a -> SDoc
ppr ModuleName
m SDoc -> SDoc -> SDoc
$$ Int -> SDoc -> SDoc
nest Int
50 ([SDoc] -> SDoc
vcat (forall a b. (a -> b) -> [a] -> [b]
map (forall a. Outputable a => ModuleName -> (Module, a) -> SDoc
pprEntry ModuleName
m) (forall k a. Map k a -> [(k, a)]
Map.toList Map Module a
e)))
      pprEntry :: Outputable a => ModuleName -> (Module, a) -> SDoc
      pprEntry :: forall a. Outputable a => ModuleName -> (Module, a) -> SDoc
pprEntry ModuleName
m (Module
m',a
o)
        | ModuleName
m forall a. Eq a => a -> a -> Bool
== forall unit. GenModule unit -> ModuleName
moduleName Module
m' = forall a. Outputable a => a -> SDoc
ppr (forall unit. GenModule unit -> unit
moduleUnit Module
m') SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
parens (forall a. Outputable a => a -> SDoc
ppr a
o)
        | Bool
otherwise = forall a. Outputable a => a -> SDoc
ppr Module
m' SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
parens (forall a. Outputable a => a -> SDoc
ppr a
o)

fsPackageName :: UnitInfo -> FastString
fsPackageName :: UnitInfo -> FastString
fsPackageName UnitInfo
info = FastString
fs
   where
      PackageName FastString
fs = forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> srcpkgname
unitPackageName UnitInfo
info


-- | Given a fully instantiated 'InstantiatedUnit', improve it into a
-- 'RealUnit' if we can find it in the package database.
improveUnit :: UnitState -> Unit -> Unit
improveUnit :: UnitState -> GenUnit UnitId -> GenUnit UnitId
improveUnit UnitState
state GenUnit UnitId
u = UnitInfoMap
-> PreloadUnitClosure -> GenUnit UnitId -> GenUnit UnitId
improveUnit' (UnitState -> UnitInfoMap
unitInfoMap UnitState
state) (UnitState -> PreloadUnitClosure
preloadClosure UnitState
state) GenUnit UnitId
u

-- | Given a fully instantiated 'InstantiatedUnit', improve it into a
-- 'RealUnit' if we can find it in the package database.
improveUnit' :: UnitInfoMap -> PreloadUnitClosure -> Unit -> Unit
improveUnit' :: UnitInfoMap
-> PreloadUnitClosure -> GenUnit UnitId -> GenUnit UnitId
improveUnit' UnitInfoMap
_       PreloadUnitClosure
_       uid :: GenUnit UnitId
uid@(RealUnit Definite UnitId
_) = GenUnit UnitId
uid -- short circuit
improveUnit' UnitInfoMap
pkg_map PreloadUnitClosure
closure GenUnit UnitId
uid =
    -- Do NOT lookup indefinite ones, they won't be useful!
    case Bool
-> UnitInfoMap
-> PreloadUnitClosure
-> GenUnit UnitId
-> Maybe UnitInfo
lookupUnit' Bool
False UnitInfoMap
pkg_map PreloadUnitClosure
closure GenUnit UnitId
uid of
        Maybe UnitInfo
Nothing  -> GenUnit UnitId
uid
        Just UnitInfo
pkg ->
            -- Do NOT improve if the indefinite unit id is not
            -- part of the closure unique set.  See
            -- Note [VirtUnit to RealUnit improvement]
            if forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId UnitInfo
pkg forall a. Uniquable a => a -> UniqSet a -> Bool
`elementOfUniqSet` PreloadUnitClosure
closure
                then UnitInfo -> GenUnit UnitId
mkUnit UnitInfo
pkg
                else GenUnit UnitId
uid

-- | Check the database to see if we already have an installed unit that
-- corresponds to the given 'InstantiatedUnit'.
--
-- Return a `UnitId` which either wraps the `InstantiatedUnit` unchanged or
-- references a matching installed unit.
--
-- See Note [VirtUnit to RealUnit improvement]
instUnitToUnit :: UnitState -> InstantiatedUnit -> Unit
instUnitToUnit :: UnitState -> GenInstantiatedUnit UnitId -> GenUnit UnitId
instUnitToUnit UnitState
state GenInstantiatedUnit UnitId
iuid =
    -- NB: suppose that we want to compare the instantiated
    -- unit p[H=impl:H] against p+abcd (where p+abcd
    -- happens to be the existing, installed version of
    -- p[H=impl:H].  If we *only* wrap in p[H=impl:H]
    -- VirtUnit, they won't compare equal; only
    -- after improvement will the equality hold.
    UnitState -> GenUnit UnitId -> GenUnit UnitId
improveUnit UnitState
state forall a b. (a -> b) -> a -> b
$ forall uid. GenInstantiatedUnit uid -> GenUnit uid
VirtUnit GenInstantiatedUnit UnitId
iuid


-- | Substitution on module variables, mapping module names to module
-- identifiers.
type ShHoleSubst = ModuleNameEnv Module

-- | Substitutes holes in a 'Module'.  NOT suitable for being called
-- directly on a 'nameModule', see Note [Representation of module/name variable].
-- @p[A=\<A>]:B@ maps to @p[A=q():A]:B@ with @A=q():A@;
-- similarly, @\<A>@ maps to @q():A@.
renameHoleModule :: UnitState -> ShHoleSubst -> Module -> Module
renameHoleModule :: UnitState -> UniqFM ModuleName Module -> Module -> Module
renameHoleModule UnitState
state = UnitInfoMap
-> PreloadUnitClosure
-> UniqFM ModuleName Module
-> Module
-> Module
renameHoleModule' (UnitState -> UnitInfoMap
unitInfoMap UnitState
state) (UnitState -> PreloadUnitClosure
preloadClosure UnitState
state)

-- | Substitutes holes in a 'Unit', suitable for renaming when
-- an include occurs; see Note [Representation of module/name variable].
--
-- @p[A=\<A>]@ maps to @p[A=\<B>]@ with @A=\<B>@.
renameHoleUnit :: UnitState -> ShHoleSubst -> Unit -> Unit
renameHoleUnit :: UnitState
-> UniqFM ModuleName Module -> GenUnit UnitId -> GenUnit UnitId
renameHoleUnit UnitState
state = UnitInfoMap
-> PreloadUnitClosure
-> UniqFM ModuleName Module
-> GenUnit UnitId
-> GenUnit UnitId
renameHoleUnit' (UnitState -> UnitInfoMap
unitInfoMap UnitState
state) (UnitState -> PreloadUnitClosure
preloadClosure UnitState
state)

-- | Like 'renameHoleModule', but requires only 'ClosureUnitInfoMap'
-- so it can be used by "GHC.Unit.State".
renameHoleModule' :: UnitInfoMap -> PreloadUnitClosure -> ShHoleSubst -> Module -> Module
renameHoleModule' :: UnitInfoMap
-> PreloadUnitClosure
-> UniqFM ModuleName Module
-> Module
-> Module
renameHoleModule' UnitInfoMap
pkg_map PreloadUnitClosure
closure UniqFM ModuleName Module
env Module
m
  | Bool -> Bool
not (forall u. GenModule (GenUnit u) -> Bool
isHoleModule Module
m) =
        let uid :: GenUnit UnitId
uid = UnitInfoMap
-> PreloadUnitClosure
-> UniqFM ModuleName Module
-> GenUnit UnitId
-> GenUnit UnitId
renameHoleUnit' UnitInfoMap
pkg_map PreloadUnitClosure
closure UniqFM ModuleName Module
env (forall unit. GenModule unit -> unit
moduleUnit Module
m)
        in forall unit. unit -> ModuleName -> GenModule unit
mkModule GenUnit UnitId
uid (forall unit. GenModule unit -> ModuleName
moduleName Module
m)
  | Just Module
m' <- forall key elt. Uniquable key => UniqFM key elt -> key -> Maybe elt
lookupUFM UniqFM ModuleName Module
env (forall unit. GenModule unit -> ModuleName
moduleName Module
m) = Module
m'
  -- NB m = <Blah>, that's what's in scope.
  | Bool
otherwise = Module
m

-- | Like 'renameHoleUnit, but requires only 'ClosureUnitInfoMap'
-- so it can be used by "GHC.Unit.State".
renameHoleUnit' :: UnitInfoMap -> PreloadUnitClosure -> ShHoleSubst -> Unit -> Unit
renameHoleUnit' :: UnitInfoMap
-> PreloadUnitClosure
-> UniqFM ModuleName Module
-> GenUnit UnitId
-> GenUnit UnitId
renameHoleUnit' UnitInfoMap
pkg_map PreloadUnitClosure
closure UniqFM ModuleName Module
env GenUnit UnitId
uid =
    case GenUnit UnitId
uid of
      (VirtUnit
        InstantiatedUnit{ instUnitInstanceOf :: forall unit. GenInstantiatedUnit unit -> Indefinite unit
instUnitInstanceOf = IndefUnitId
cid
                        , instUnitInsts :: forall unit. GenInstantiatedUnit unit -> GenInstantiations unit
instUnitInsts      = [(ModuleName, Module)]
insts
                        , instUnitHoles :: forall unit. GenInstantiatedUnit unit -> UniqDSet ModuleName
instUnitHoles      = UniqDSet ModuleName
fh })
          -> if forall key elt. UniqFM key elt -> Bool
isNullUFM (forall elt1 elt2 elt3 key.
(elt1 -> elt2 -> elt3)
-> UniqFM key elt1 -> UniqFM key elt2 -> UniqFM key elt3
intersectUFM_C forall a b. a -> b -> a
const (forall key elt. UniqDFM key elt -> UniqFM key elt
udfmToUfm (forall a. UniqDSet a -> UniqDFM a a
getUniqDSet UniqDSet ModuleName
fh)) UniqFM ModuleName Module
env)
                then GenUnit UnitId
uid
                -- Functorially apply the substitution to the instantiation,
                -- then check the 'ClosureUnitInfoMap' to see if there is
                -- a compiled version of this 'InstantiatedUnit' we can improve to.
                -- See Note [VirtUnit to RealUnit improvement]
                else UnitInfoMap
-> PreloadUnitClosure -> GenUnit UnitId -> GenUnit UnitId
improveUnit' UnitInfoMap
pkg_map PreloadUnitClosure
closure forall a b. (a -> b) -> a -> b
$
                        forall u.
IsUnitId u =>
Indefinite u -> [(ModuleName, GenModule (GenUnit u))] -> GenUnit u
mkVirtUnit IndefUnitId
cid
                            (forall a b. (a -> b) -> [a] -> [b]
map (\(ModuleName
k,Module
v) -> (ModuleName
k, UnitInfoMap
-> PreloadUnitClosure
-> UniqFM ModuleName Module
-> Module
-> Module
renameHoleModule' UnitInfoMap
pkg_map PreloadUnitClosure
closure UniqFM ModuleName Module
env Module
v)) [(ModuleName, Module)]
insts)
      GenUnit UnitId
_ -> GenUnit UnitId
uid

-- | Injects an 'InstantiatedModule' to 'Module' (see also
-- 'instUnitToUnit'.
instModuleToModule :: UnitState -> InstantiatedModule -> Module
instModuleToModule :: UnitState -> InstantiatedModule -> Module
instModuleToModule UnitState
pkgstate (Module GenInstantiatedUnit UnitId
iuid ModuleName
mod_name) =
    forall unit. unit -> ModuleName -> GenModule unit
mkModule (UnitState -> GenInstantiatedUnit UnitId -> GenUnit UnitId
instUnitToUnit UnitState
pkgstate GenInstantiatedUnit UnitId
iuid) ModuleName
mod_name

-- | Print unit-ids with UnitInfo found in the given UnitState
pprWithUnitState :: UnitState -> SDoc -> SDoc
pprWithUnitState :: UnitState -> SDoc -> SDoc
pprWithUnitState UnitState
state = (SDocContext -> SDocContext) -> SDoc -> SDoc
updSDocContext (\SDocContext
ctx -> SDocContext
ctx
   { sdocUnitIdForUser :: FastString -> SDoc
sdocUnitIdForUser = \FastString
fs -> UnitState -> UnitId -> SDoc
pprUnitIdForUser UnitState
state (FastString -> UnitId
UnitId FastString
fs)
   })