{-# LANGUAGE CPP, ScopedTypeVariables #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns #-}
module HscTypes (
        
        HscEnv(..), hscEPS,
        FinderCache, FindResult(..), InstalledFindResult(..),
        Target(..), TargetId(..), InputFileBuffer, pprTarget, pprTargetId,
        HscStatus(..),
        IServ(..),
        
        ModuleGraph, emptyMG, mkModuleGraph, extendMG, mapMG,
        mgModSummaries, mgElemModule, mgLookupModule,
        needsTemplateHaskellOrQQ, mgBootModules,
        
        Hsc(..), runHsc, mkInteractiveHscEnv, runInteractiveHsc,
        
        ModDetails(..), emptyModDetails,
        ModGuts(..), CgGuts(..), ForeignStubs(..), appendStubC,
        ImportedMods, ImportedBy(..), importedByUser, ImportedModsVal(..), SptEntry(..),
        ForeignSrcLang(..),
        ModSummary(..), ms_imps, ms_installed_mod, ms_mod_name, showModMsg, isBootSummary,
        msHsFilePath, msHiFilePath, msObjFilePath,
        SourceModified(..), isTemplateHaskellOrQQNonBoot,
        
        
        HscSource(..), isHsBootOrSig, isHsigFile, hscSourceString,
        
        HomePackageTable, HomeModInfo(..), emptyHomePackageTable,
        lookupHpt, eltsHpt, filterHpt, allHpt, mapHpt, delFromHpt,
        addToHpt, addListToHpt, lookupHptDirectly, listToHpt,
        hptCompleteSigs,
        hptInstances, hptRules, pprHPT,
        
        ExternalPackageState(..), EpsStats(..), addEpsInStats,
        PackageTypeEnv, PackageIfaceTable, emptyPackageIfaceTable,
        lookupIfaceByModule, emptyModIface, lookupHptByModule,
        PackageInstEnv, PackageFamInstEnv, PackageRuleBase,
        PackageCompleteMatchMap,
        mkSOName, mkHsSOName, soExt,
        
        MetaRequest(..),
        MetaResult, 
        metaRequestE, metaRequestP, metaRequestT, metaRequestD, metaRequestAW,
        MetaHook,
        
        prepareAnnotations,
        
        InteractiveContext(..), emptyInteractiveContext,
        icPrintUnqual, icInScopeTTs, icExtendGblRdrEnv,
        extendInteractiveContext, extendInteractiveContextWithIds,
        substInteractiveContext,
        setInteractivePrintName, icInteractiveModule,
        InteractiveImport(..), setInteractivePackage,
        mkPrintUnqualified, pprModulePrefix,
        mkQualPackage, mkQualModule, pkgQual,
        
        ModIface(..), mkIfaceWarnCache, mkIfaceHashCache, mkIfaceFixCache,
        emptyIfaceWarnCache, mi_boot, mi_fix,
        mi_semantic_module,
        mi_free_holes,
        renameFreeHoles,
        
        FixityEnv, FixItem(..), lookupFixity, emptyFixityEnv,
        
        TyThing(..),  tyThingAvailInfo,
        tyThingTyCon, tyThingDataCon, tyThingConLike,
        tyThingId, tyThingCoAxiom, tyThingParent_maybe, tyThingsTyCoVars,
        implicitTyThings, implicitTyConThings, implicitClassThings,
        isImplicitTyThing,
        TypeEnv, lookupType, lookupTypeHscEnv, mkTypeEnv, emptyTypeEnv,
        typeEnvFromEntities, mkTypeEnvWithImplicits,
        extendTypeEnv, extendTypeEnvList,
        extendTypeEnvWithIds, plusTypeEnv,
        lookupTypeEnv,
        typeEnvElts, typeEnvTyCons, typeEnvIds, typeEnvPatSyns,
        typeEnvDataCons, typeEnvCoAxioms, typeEnvClasses,
        
        MonadThings(..),
        
        WhetherHasOrphans, IsBootInterface, Usage(..),
        Dependencies(..), noDependencies,
        updNameCache,
        IfaceExport,
        
        Warnings(..), WarningTxt(..), plusWarns,
        
        Linkable(..), isObjectLinkable, linkableObjs,
        Unlinked(..), CompiledByteCode,
        isObject, nameOfObject, isInterpretable, byteCodeOfObject,
        
        HpcInfo(..), emptyHpcInfo, isHpcUsed, AnyHpcUsage,
        
        ModBreaks (..), emptyModBreaks,
        
        IfaceTrustInfo, getSafeMode, setSafeMode, noIfaceTrustInfo,
        trustInfoToNum, numToTrustInfo, IsSafeImport,
        
        HsParsedModule(..),
        
        SourceError, GhcApiError, mkSrcErr, srcErrorMessages, mkApiErr,
        throwErrors, throwOneError, handleSourceError,
        handleFlagWarnings, printOrThrowWarnings,
        
        CompleteMatch(..), CompleteMatchMap,
        mkCompleteMatchMap, extendCompleteMatchMap
    ) where
#include "HsVersions.h"
import GhcPrelude
import ByteCodeTypes
import InteractiveEvalTypes ( Resume )
import GHCi.Message         ( Pipe )
import GHCi.RemoteTypes
import GHC.ForeignSrcLang
import UniqFM
import HsSyn
import RdrName
import Avail
import Module
import InstEnv          ( InstEnv, ClsInst, identicalClsInstHead )
import FamInstEnv
import CoreSyn          ( CoreProgram, RuleBase, CoreRule )
import Name
import NameEnv
import VarSet
import Var
import Id
import IdInfo           ( IdDetails(..), RecSelParent(..))
import Type
import ApiAnnotation    ( ApiAnns )
import Annotations      ( Annotation, AnnEnv, mkAnnEnv, plusAnnEnv )
import Class
import TyCon
import CoAxiom
import ConLike
import DataCon
import PatSyn
import PrelNames        ( gHC_PRIM, ioTyConName, printName, mkInteractiveModule )
import TysWiredIn
import Packages hiding  ( Version(..) )
import CmdLineParser
import DynFlags
import DriverPhases     ( Phase, HscSource(..), hscSourceString
                        , isHsBootOrSig, isHsigFile )
import BasicTypes
import IfaceSyn
import Maybes
import Outputable
import SrcLoc
import Unique
import UniqDFM
import FastString
import StringBuffer     ( StringBuffer )
import Fingerprint
import MonadUtils
import Bag
import Binary
import ErrUtils
import NameCache
import Platform
import Util
import UniqDSet
import GHC.Serialized   ( Serialized )
import qualified GHC.LanguageExtensions as LangExt
import Foreign
import Control.Monad    ( guard, liftM, ap )
import Data.IORef
import Data.Time
import Exception
import System.FilePath
import Control.Concurrent
import System.Process   ( ProcessHandle )
data HscStatus
    = HscNotGeneratingCode
    | HscUpToDate
    | HscUpdateBoot
    | HscUpdateSig
    | HscRecomp CgGuts ModSummary
newtype Hsc a = Hsc (HscEnv -> WarningMessages -> IO (a, WarningMessages))
instance Functor Hsc where
    fmap :: (a -> b) -> Hsc a -> Hsc b
fmap = (a -> b) -> Hsc a -> Hsc b
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM
instance Applicative Hsc where
    pure :: a -> Hsc a
pure a :: a
a = (HscEnv -> WarningMessages -> IO (a, WarningMessages)) -> Hsc a
forall a.
(HscEnv -> WarningMessages -> IO (a, WarningMessages)) -> Hsc a
Hsc ((HscEnv -> WarningMessages -> IO (a, WarningMessages)) -> Hsc a)
-> (HscEnv -> WarningMessages -> IO (a, WarningMessages)) -> Hsc a
forall a b. (a -> b) -> a -> b
$ \_ w :: WarningMessages
w -> (a, WarningMessages) -> IO (a, WarningMessages)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
a, WarningMessages
w)
    <*> :: Hsc (a -> b) -> Hsc a -> Hsc b
(<*>) = Hsc (a -> b) -> Hsc a -> Hsc b
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
ap
instance Monad Hsc where
    Hsc m :: HscEnv -> WarningMessages -> IO (a, WarningMessages)
m >>= :: Hsc a -> (a -> Hsc b) -> Hsc b
>>= k :: a -> Hsc b
k = (HscEnv -> WarningMessages -> IO (b, WarningMessages)) -> Hsc b
forall a.
(HscEnv -> WarningMessages -> IO (a, WarningMessages)) -> Hsc a
Hsc ((HscEnv -> WarningMessages -> IO (b, WarningMessages)) -> Hsc b)
-> (HscEnv -> WarningMessages -> IO (b, WarningMessages)) -> Hsc b
forall a b. (a -> b) -> a -> b
$ \e :: HscEnv
e w :: WarningMessages
w -> do (a :: a
a, w1 :: WarningMessages
w1) <- HscEnv -> WarningMessages -> IO (a, WarningMessages)
m HscEnv
e WarningMessages
w
                                   case a -> Hsc b
k a
a of
                                       Hsc k' :: HscEnv -> WarningMessages -> IO (b, WarningMessages)
k' -> HscEnv -> WarningMessages -> IO (b, WarningMessages)
k' HscEnv
e WarningMessages
w1
instance MonadIO Hsc where
    liftIO :: IO a -> Hsc a
liftIO io :: IO a
io = (HscEnv -> WarningMessages -> IO (a, WarningMessages)) -> Hsc a
forall a.
(HscEnv -> WarningMessages -> IO (a, WarningMessages)) -> Hsc a
Hsc ((HscEnv -> WarningMessages -> IO (a, WarningMessages)) -> Hsc a)
-> (HscEnv -> WarningMessages -> IO (a, WarningMessages)) -> Hsc a
forall a b. (a -> b) -> a -> b
$ \_ w :: WarningMessages
w -> do a
a <- IO a
io; (a, WarningMessages) -> IO (a, WarningMessages)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
a, WarningMessages
w)
instance HasDynFlags Hsc where
    getDynFlags :: Hsc DynFlags
getDynFlags = (HscEnv -> WarningMessages -> IO (DynFlags, WarningMessages))
-> Hsc DynFlags
forall a.
(HscEnv -> WarningMessages -> IO (a, WarningMessages)) -> Hsc a
Hsc ((HscEnv -> WarningMessages -> IO (DynFlags, WarningMessages))
 -> Hsc DynFlags)
-> (HscEnv -> WarningMessages -> IO (DynFlags, WarningMessages))
-> Hsc DynFlags
forall a b. (a -> b) -> a -> b
$ \e :: HscEnv
e w :: WarningMessages
w -> (DynFlags, WarningMessages) -> IO (DynFlags, WarningMessages)
forall (m :: * -> *) a. Monad m => a -> m a
return (HscEnv -> DynFlags
hsc_dflags HscEnv
e, WarningMessages
w)
runHsc :: HscEnv -> Hsc a -> IO a
runHsc :: HscEnv -> Hsc a -> IO a
runHsc hsc_env :: HscEnv
hsc_env (Hsc hsc :: HscEnv -> WarningMessages -> IO (a, WarningMessages)
hsc) = do
    (a :: a
a, w :: WarningMessages
w) <- HscEnv -> WarningMessages -> IO (a, WarningMessages)
hsc HscEnv
hsc_env WarningMessages
forall a. Bag a
emptyBag
    DynFlags -> WarningMessages -> IO ()
printOrThrowWarnings (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env) WarningMessages
w
    a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
mkInteractiveHscEnv :: HscEnv -> HscEnv
mkInteractiveHscEnv :: HscEnv -> HscEnv
mkInteractiveHscEnv hsc_env :: HscEnv
hsc_env = HscEnv
hsc_env{ hsc_dflags :: DynFlags
hsc_dflags = DynFlags
interactive_dflags }
  where
    interactive_dflags :: DynFlags
interactive_dflags = InteractiveContext -> DynFlags
ic_dflags (HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env)
runInteractiveHsc :: HscEnv -> Hsc a -> IO a
runInteractiveHsc :: HscEnv -> Hsc a -> IO a
runInteractiveHsc hsc_env :: HscEnv
hsc_env = HscEnv -> Hsc a -> IO a
forall a. HscEnv -> Hsc a -> IO a
runHsc (HscEnv -> HscEnv
mkInteractiveHscEnv HscEnv
hsc_env)
mkSrcErr :: ErrorMessages -> SourceError
mkSrcErr :: WarningMessages -> SourceError
mkSrcErr = WarningMessages -> SourceError
SourceError
srcErrorMessages :: SourceError -> ErrorMessages
srcErrorMessages :: SourceError -> WarningMessages
srcErrorMessages (SourceError msgs :: WarningMessages
msgs) = WarningMessages
msgs
mkApiErr :: DynFlags -> SDoc -> GhcApiError
mkApiErr :: DynFlags -> SDoc -> GhcApiError
mkApiErr dflags :: DynFlags
dflags msg :: SDoc
msg = String -> GhcApiError
GhcApiError (DynFlags -> SDoc -> String
showSDoc DynFlags
dflags SDoc
msg)
throwErrors :: MonadIO io => ErrorMessages -> io a
throwErrors :: WarningMessages -> io a
throwErrors = IO a -> io a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO a -> io a)
-> (WarningMessages -> IO a) -> WarningMessages -> io a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SourceError -> IO a
forall e a. Exception e => e -> IO a
throwIO (SourceError -> IO a)
-> (WarningMessages -> SourceError) -> WarningMessages -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WarningMessages -> SourceError
mkSrcErr
throwOneError :: MonadIO m => ErrMsg -> m ab
throwOneError :: ErrMsg -> m ab
throwOneError err :: ErrMsg
err = IO ab -> m ab
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ab -> m ab) -> IO ab -> m ab
forall a b. (a -> b) -> a -> b
$ SourceError -> IO ab
forall e a. Exception e => e -> IO a
throwIO (SourceError -> IO ab) -> SourceError -> IO ab
forall a b. (a -> b) -> a -> b
$ WarningMessages -> SourceError
mkSrcErr (WarningMessages -> SourceError) -> WarningMessages -> SourceError
forall a b. (a -> b) -> a -> b
$ ErrMsg -> WarningMessages
forall a. a -> Bag a
unitBag ErrMsg
err
newtype SourceError = SourceError ErrorMessages
instance Show SourceError where
  show :: SourceError -> String
show (SourceError msgs :: WarningMessages
msgs) = [String] -> String
unlines ([String] -> String)
-> (WarningMessages -> [String]) -> WarningMessages -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ErrMsg -> String) -> [ErrMsg] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map ErrMsg -> String
forall a. Show a => a -> String
show ([ErrMsg] -> [String])
-> (WarningMessages -> [ErrMsg]) -> WarningMessages -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WarningMessages -> [ErrMsg]
forall a. Bag a -> [a]
bagToList (WarningMessages -> String) -> WarningMessages -> String
forall a b. (a -> b) -> a -> b
$ WarningMessages
msgs
instance Exception SourceError
handleSourceError :: (ExceptionMonad m) =>
                     (SourceError -> m a) 
                  -> m a 
                  -> m a
handleSourceError :: (SourceError -> m a) -> m a -> m a
handleSourceError handler :: SourceError -> m a
handler act :: m a
act =
  m a -> (SourceError -> m a) -> m a
forall (m :: * -> *) e a.
(ExceptionMonad m, Exception e) =>
m a -> (e -> m a) -> m a
gcatch m a
act (\(SourceError
e :: SourceError) -> SourceError -> m a
handler SourceError
e)
newtype GhcApiError = GhcApiError String
instance Show GhcApiError where
  show :: GhcApiError -> String
show (GhcApiError msg :: String
msg) = String
msg
instance Exception GhcApiError
printOrThrowWarnings :: DynFlags -> Bag WarnMsg -> IO ()
printOrThrowWarnings :: DynFlags -> WarningMessages -> IO ()
printOrThrowWarnings dflags :: DynFlags
dflags warns :: WarningMessages
warns = do
  let (make_error :: Bool
make_error, warns' :: WarningMessages
warns') =
        (Bool -> ErrMsg -> (Bool, ErrMsg))
-> Bool -> WarningMessages -> (Bool, WarningMessages)
forall acc x y.
(acc -> x -> (acc, y)) -> acc -> Bag x -> (acc, Bag y)
mapAccumBagL
          (\make_err :: Bool
make_err warn :: ErrMsg
warn ->
            case DynFlags -> ErrMsg -> Maybe (Maybe WarningFlag)
isWarnMsgFatal DynFlags
dflags ErrMsg
warn of
              Nothing ->
                (Bool
make_err, ErrMsg
warn)
              Just err_reason :: Maybe WarningFlag
err_reason ->
                (Bool
True, ErrMsg
warn{ errMsgSeverity :: Severity
errMsgSeverity = Severity
SevError
                           , errMsgReason :: WarnReason
errMsgReason = Maybe WarningFlag -> WarnReason
ErrReason Maybe WarningFlag
err_reason
                           }))
          Bool
False WarningMessages
warns
  if Bool
make_error
    then SourceError -> IO ()
forall e a. Exception e => e -> IO a
throwIO (WarningMessages -> SourceError
mkSrcErr WarningMessages
warns')
    else DynFlags -> WarningMessages -> IO ()
printBagOfErrors DynFlags
dflags WarningMessages
warns
handleFlagWarnings :: DynFlags -> [Warn] -> IO ()
handleFlagWarnings :: DynFlags -> [Warn] -> IO ()
handleFlagWarnings dflags :: DynFlags
dflags warns :: [Warn]
warns = do
  let warns' :: [Warn]
warns' = (Warn -> Bool) -> [Warn] -> [Warn]
forall a. (a -> Bool) -> [a] -> [a]
filter (DynFlags -> WarnReason -> Bool
shouldPrintWarning DynFlags
dflags (WarnReason -> Bool) -> (Warn -> WarnReason) -> Warn -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Warn -> WarnReason
warnReason)  [Warn]
warns
      
      
      bag :: WarningMessages
bag = [ErrMsg] -> WarningMessages
forall a. [a] -> Bag a
listToBag [ DynFlags -> SrcSpan -> SDoc -> ErrMsg
mkPlainWarnMsg DynFlags
dflags SrcSpan
loc (String -> SDoc
text String
SrcSpanLess (Located String)
warn)
                      | Warn _ (Located String -> Located (SrcSpanLess (Located String))
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L loc :: SrcSpan
loc warn :: SrcSpanLess (Located String)
warn) <- [Warn]
warns' ]
  DynFlags -> WarningMessages -> IO ()
printOrThrowWarnings DynFlags
dflags WarningMessages
bag
shouldPrintWarning :: DynFlags -> CmdLineParser.WarnReason -> Bool
shouldPrintWarning :: DynFlags -> WarnReason -> Bool
shouldPrintWarning dflags :: DynFlags
dflags ReasonDeprecatedFlag
  = WarningFlag -> DynFlags -> Bool
wopt WarningFlag
Opt_WarnDeprecatedFlags DynFlags
dflags
shouldPrintWarning dflags :: DynFlags
dflags ReasonUnrecognisedFlag
  = WarningFlag -> DynFlags -> Bool
wopt WarningFlag
Opt_WarnUnrecognisedWarningFlags DynFlags
dflags
shouldPrintWarning _ _
  = Bool
True
data HscEnv
  = HscEnv {
        HscEnv -> DynFlags
hsc_dflags :: DynFlags,
                
        HscEnv -> [Target]
hsc_targets :: [Target],
                
        HscEnv -> ModuleGraph
hsc_mod_graph :: ModuleGraph,
                
        HscEnv -> InteractiveContext
hsc_IC :: InteractiveContext,
                
        HscEnv -> HomePackageTable
hsc_HPT    :: HomePackageTable,
                
                
                
                
                
                
                
                
                
                
                
                
                
                
                
                
                
                
        HscEnv -> IORef ExternalPackageState
hsc_EPS :: {-# UNPACK #-} !(IORef ExternalPackageState),
                
                
                
        HscEnv -> IORef NameCache
hsc_NC  :: {-# UNPACK #-} !(IORef NameCache),
                
                
                
        HscEnv -> IORef FinderCache
hsc_FC   :: {-# UNPACK #-} !(IORef FinderCache),
                
        HscEnv -> Maybe (Module, IORef TypeEnv)
hsc_type_env_var :: Maybe (Module, IORef TypeEnv)
                
                
                
        , HscEnv -> MVar (Maybe IServ)
hsc_iserv :: MVar (Maybe IServ)
                
                
 }
data IServ = IServ
  { IServ -> Pipe
iservPipe :: Pipe
  , IServ -> ProcessHandle
iservProcess :: ProcessHandle
  , IServ -> IORef (UniqFM (Ptr ()))
iservLookupSymbolCache :: IORef (UniqFM (Ptr ()))
  , IServ -> [HValueRef]
iservPendingFrees :: [HValueRef]
  }
hscEPS :: HscEnv -> IO ExternalPackageState
hscEPS :: HscEnv -> IO ExternalPackageState
hscEPS hsc_env :: HscEnv
hsc_env = IORef ExternalPackageState -> IO ExternalPackageState
forall a. IORef a -> IO a
readIORef (HscEnv -> IORef ExternalPackageState
hsc_EPS HscEnv
hsc_env)
data Target
  = Target {
      Target -> TargetId
targetId           :: TargetId, 
      Target -> Bool
targetAllowObjCode :: Bool,     
      Target -> Maybe (InputFileBuffer, UTCTime)
targetContents     :: Maybe (InputFileBuffer, UTCTime)
      
      
      
      
      
      
      
      
      
      
    }
data TargetId
  = TargetModule ModuleName
        
  | TargetFile FilePath (Maybe Phase)
        
        
        
        
  deriving TargetId -> TargetId -> Bool
(TargetId -> TargetId -> Bool)
-> (TargetId -> TargetId -> Bool) -> Eq TargetId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TargetId -> TargetId -> Bool
$c/= :: TargetId -> TargetId -> Bool
== :: TargetId -> TargetId -> Bool
$c== :: TargetId -> TargetId -> Bool
Eq
type InputFileBuffer = StringBuffer
pprTarget :: Target -> SDoc
pprTarget :: Target -> SDoc
pprTarget (Target id :: TargetId
id obj :: Bool
obj _) =
    (if Bool
obj then Char -> SDoc
char '*' else SDoc
empty) SDoc -> SDoc -> SDoc
<> TargetId -> SDoc
pprTargetId TargetId
id
instance Outputable Target where
    ppr :: Target -> SDoc
ppr = Target -> SDoc
pprTarget
pprTargetId :: TargetId -> SDoc
pprTargetId :: TargetId -> SDoc
pprTargetId (TargetModule m :: ModuleName
m) = ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
m
pprTargetId (TargetFile f :: String
f _) = String -> SDoc
text String
f
instance Outputable TargetId where
    ppr :: TargetId -> SDoc
ppr = TargetId -> SDoc
pprTargetId
type HomePackageTable  = DModuleNameEnv HomeModInfo
        
        
type PackageIfaceTable = ModuleEnv ModIface
        
emptyHomePackageTable :: HomePackageTable
emptyHomePackageTable :: HomePackageTable
emptyHomePackageTable  = HomePackageTable
forall elt. UniqDFM elt
emptyUDFM
emptyPackageIfaceTable :: PackageIfaceTable
emptyPackageIfaceTable :: PackageIfaceTable
emptyPackageIfaceTable = PackageIfaceTable
forall a. ModuleEnv a
emptyModuleEnv
pprHPT :: HomePackageTable -> SDoc
pprHPT :: HomePackageTable -> SDoc
pprHPT hpt :: HomePackageTable
hpt = HomePackageTable -> ([HomeModInfo] -> SDoc) -> SDoc
forall a. UniqDFM a -> ([a] -> SDoc) -> SDoc
pprUDFM HomePackageTable
hpt (([HomeModInfo] -> SDoc) -> SDoc)
-> ([HomeModInfo] -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \hms :: [HomeModInfo]
hms ->
    [SDoc] -> SDoc
vcat [ SDoc -> Int -> SDoc -> SDoc
hang (Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr (ModIface -> Module
mi_module (HomeModInfo -> ModIface
hm_iface HomeModInfo
hm)))
              2 (TypeEnv -> SDoc
forall a. Outputable a => a -> SDoc
ppr (ModDetails -> TypeEnv
md_types (HomeModInfo -> ModDetails
hm_details HomeModInfo
hm)))
         | HomeModInfo
hm <- [HomeModInfo]
hms ]
lookupHpt :: HomePackageTable -> ModuleName -> Maybe HomeModInfo
lookupHpt :: HomePackageTable -> ModuleName -> Maybe HomeModInfo
lookupHpt = HomePackageTable -> ModuleName -> Maybe HomeModInfo
forall key elt. Uniquable key => UniqDFM elt -> key -> Maybe elt
lookupUDFM
lookupHptDirectly :: HomePackageTable -> Unique -> Maybe HomeModInfo
lookupHptDirectly :: HomePackageTable -> Unique -> Maybe HomeModInfo
lookupHptDirectly = HomePackageTable -> Unique -> Maybe HomeModInfo
forall elt. UniqDFM elt -> Unique -> Maybe elt
lookupUDFM_Directly
eltsHpt :: HomePackageTable -> [HomeModInfo]
eltsHpt :: HomePackageTable -> [HomeModInfo]
eltsHpt = HomePackageTable -> [HomeModInfo]
forall elt. UniqDFM elt -> [elt]
eltsUDFM
filterHpt :: (HomeModInfo -> Bool) -> HomePackageTable -> HomePackageTable
filterHpt :: (HomeModInfo -> Bool) -> HomePackageTable -> HomePackageTable
filterHpt = (HomeModInfo -> Bool) -> HomePackageTable -> HomePackageTable
forall elt. (elt -> Bool) -> UniqDFM elt -> UniqDFM elt
filterUDFM
allHpt :: (HomeModInfo -> Bool) -> HomePackageTable -> Bool
allHpt :: (HomeModInfo -> Bool) -> HomePackageTable -> Bool
allHpt = (HomeModInfo -> Bool) -> HomePackageTable -> Bool
forall elt. (elt -> Bool) -> UniqDFM elt -> Bool
allUDFM
mapHpt :: (HomeModInfo -> HomeModInfo) -> HomePackageTable -> HomePackageTable
mapHpt :: (HomeModInfo -> HomeModInfo)
-> HomePackageTable -> HomePackageTable
mapHpt = (HomeModInfo -> HomeModInfo)
-> HomePackageTable -> HomePackageTable
forall elt1 elt2. (elt1 -> elt2) -> UniqDFM elt1 -> UniqDFM elt2
mapUDFM
delFromHpt :: HomePackageTable -> ModuleName -> HomePackageTable
delFromHpt :: HomePackageTable -> ModuleName -> HomePackageTable
delFromHpt = HomePackageTable -> ModuleName -> HomePackageTable
forall key elt. Uniquable key => UniqDFM elt -> key -> UniqDFM elt
delFromUDFM
addToHpt :: HomePackageTable -> ModuleName -> HomeModInfo -> HomePackageTable
addToHpt :: HomePackageTable -> ModuleName -> HomeModInfo -> HomePackageTable
addToHpt = HomePackageTable -> ModuleName -> HomeModInfo -> HomePackageTable
forall key elt.
Uniquable key =>
UniqDFM elt -> key -> elt -> UniqDFM elt
addToUDFM
addListToHpt
  :: HomePackageTable -> [(ModuleName, HomeModInfo)] -> HomePackageTable
addListToHpt :: HomePackageTable -> [(ModuleName, HomeModInfo)] -> HomePackageTable
addListToHpt = HomePackageTable -> [(ModuleName, HomeModInfo)] -> HomePackageTable
forall key elt.
Uniquable key =>
UniqDFM elt -> [(key, elt)] -> UniqDFM elt
addListToUDFM
listToHpt :: [(ModuleName, HomeModInfo)] -> HomePackageTable
listToHpt :: [(ModuleName, HomeModInfo)] -> HomePackageTable
listToHpt = [(ModuleName, HomeModInfo)] -> HomePackageTable
forall key elt. Uniquable key => [(key, elt)] -> UniqDFM elt
listToUDFM
lookupHptByModule :: HomePackageTable -> Module -> Maybe HomeModInfo
lookupHptByModule :: HomePackageTable -> Module -> Maybe HomeModInfo
lookupHptByModule hpt :: HomePackageTable
hpt mod :: Module
mod
  = case HomePackageTable -> ModuleName -> Maybe HomeModInfo
lookupHpt HomePackageTable
hpt (Module -> ModuleName
moduleName Module
mod) of
      Just hm :: HomeModInfo
hm | ModIface -> Module
mi_module (HomeModInfo -> ModIface
hm_iface HomeModInfo
hm) Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
== Module
mod -> HomeModInfo -> Maybe HomeModInfo
forall a. a -> Maybe a
Just HomeModInfo
hm
      _otherwise :: Maybe HomeModInfo
_otherwise                               -> Maybe HomeModInfo
forall a. Maybe a
Nothing
data HomeModInfo
  = HomeModInfo {
      HomeModInfo -> ModIface
hm_iface    :: !ModIface,
        
        
      HomeModInfo -> ModDetails
hm_details  :: !ModDetails,
        
        
      HomeModInfo -> Maybe Linkable
hm_linkable :: !(Maybe Linkable)
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
    }
lookupIfaceByModule
        :: DynFlags
        -> HomePackageTable
        -> PackageIfaceTable
        -> Module
        -> Maybe ModIface
lookupIfaceByModule :: DynFlags
-> HomePackageTable
-> PackageIfaceTable
-> Module
-> Maybe ModIface
lookupIfaceByModule _dflags :: DynFlags
_dflags hpt :: HomePackageTable
hpt pit :: PackageIfaceTable
pit mod :: Module
mod
  = case HomePackageTable -> Module -> Maybe HomeModInfo
lookupHptByModule HomePackageTable
hpt Module
mod of
       Just hm :: HomeModInfo
hm -> ModIface -> Maybe ModIface
forall a. a -> Maybe a
Just (HomeModInfo -> ModIface
hm_iface HomeModInfo
hm)
       Nothing -> PackageIfaceTable -> Module -> Maybe ModIface
forall a. ModuleEnv a -> Module -> Maybe a
lookupModuleEnv PackageIfaceTable
pit Module
mod
hptCompleteSigs :: HscEnv -> [CompleteMatch]
hptCompleteSigs :: HscEnv -> [CompleteMatch]
hptCompleteSigs = (HomeModInfo -> [CompleteMatch]) -> HscEnv -> [CompleteMatch]
forall a. (HomeModInfo -> [a]) -> HscEnv -> [a]
hptAllThings  (ModDetails -> [CompleteMatch]
md_complete_sigs (ModDetails -> [CompleteMatch])
-> (HomeModInfo -> ModDetails) -> HomeModInfo -> [CompleteMatch]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HomeModInfo -> ModDetails
hm_details)
hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([ClsInst], [FamInst])
hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([ClsInst], [FamInst])
hptInstances hsc_env :: HscEnv
hsc_env want_this_module :: ModuleName -> Bool
want_this_module
  = let (insts :: [[ClsInst]]
insts, famInsts :: [[FamInst]]
famInsts) = [([ClsInst], [FamInst])] -> ([[ClsInst]], [[FamInst]])
forall a b. [(a, b)] -> ([a], [b])
unzip ([([ClsInst], [FamInst])] -> ([[ClsInst]], [[FamInst]]))
-> [([ClsInst], [FamInst])] -> ([[ClsInst]], [[FamInst]])
forall a b. (a -> b) -> a -> b
$ ((HomeModInfo -> [([ClsInst], [FamInst])])
 -> HscEnv -> [([ClsInst], [FamInst])])
-> HscEnv
-> (HomeModInfo -> [([ClsInst], [FamInst])])
-> [([ClsInst], [FamInst])]
forall a b c. (a -> b -> c) -> b -> a -> c
flip (HomeModInfo -> [([ClsInst], [FamInst])])
-> HscEnv -> [([ClsInst], [FamInst])]
forall a. (HomeModInfo -> [a]) -> HscEnv -> [a]
hptAllThings HscEnv
hsc_env ((HomeModInfo -> [([ClsInst], [FamInst])])
 -> [([ClsInst], [FamInst])])
-> (HomeModInfo -> [([ClsInst], [FamInst])])
-> [([ClsInst], [FamInst])]
forall a b. (a -> b) -> a -> b
$ \mod_info :: HomeModInfo
mod_info -> do
                Bool -> [()]
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (ModuleName -> Bool
want_this_module (Module -> ModuleName
moduleName (ModIface -> Module
mi_module (HomeModInfo -> ModIface
hm_iface HomeModInfo
mod_info))))
                let details :: ModDetails
details = HomeModInfo -> ModDetails
hm_details HomeModInfo
mod_info
                ([ClsInst], [FamInst]) -> [([ClsInst], [FamInst])]
forall (m :: * -> *) a. Monad m => a -> m a
return (ModDetails -> [ClsInst]
md_insts ModDetails
details, ModDetails -> [FamInst]
md_fam_insts ModDetails
details)
    in ([[ClsInst]] -> [ClsInst]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[ClsInst]]
insts, [[FamInst]] -> [FamInst]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[FamInst]]
famInsts)
hptRules :: HscEnv -> [(ModuleName, IsBootInterface)] -> [CoreRule]
hptRules :: HscEnv -> [(ModuleName, Bool)] -> [CoreRule]
hptRules = (HomeModInfo -> [CoreRule])
-> Bool -> HscEnv -> [(ModuleName, Bool)] -> [CoreRule]
forall a.
(HomeModInfo -> [a])
-> Bool -> HscEnv -> [(ModuleName, Bool)] -> [a]
hptSomeThingsBelowUs (ModDetails -> [CoreRule]
md_rules (ModDetails -> [CoreRule])
-> (HomeModInfo -> ModDetails) -> HomeModInfo -> [CoreRule]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HomeModInfo -> ModDetails
hm_details) Bool
False
hptAnns :: HscEnv -> Maybe [(ModuleName, IsBootInterface)] -> [Annotation]
hptAnns :: HscEnv -> Maybe [(ModuleName, Bool)] -> [Annotation]
hptAnns hsc_env :: HscEnv
hsc_env (Just deps :: [(ModuleName, Bool)]
deps) = (HomeModInfo -> [Annotation])
-> Bool -> HscEnv -> [(ModuleName, Bool)] -> [Annotation]
forall a.
(HomeModInfo -> [a])
-> Bool -> HscEnv -> [(ModuleName, Bool)] -> [a]
hptSomeThingsBelowUs (ModDetails -> [Annotation]
md_anns (ModDetails -> [Annotation])
-> (HomeModInfo -> ModDetails) -> HomeModInfo -> [Annotation]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HomeModInfo -> ModDetails
hm_details) Bool
False HscEnv
hsc_env [(ModuleName, Bool)]
deps
hptAnns hsc_env :: HscEnv
hsc_env Nothing = (HomeModInfo -> [Annotation]) -> HscEnv -> [Annotation]
forall a. (HomeModInfo -> [a]) -> HscEnv -> [a]
hptAllThings (ModDetails -> [Annotation]
md_anns (ModDetails -> [Annotation])
-> (HomeModInfo -> ModDetails) -> HomeModInfo -> [Annotation]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HomeModInfo -> ModDetails
hm_details) HscEnv
hsc_env
hptAllThings :: (HomeModInfo -> [a]) -> HscEnv -> [a]
hptAllThings :: (HomeModInfo -> [a]) -> HscEnv -> [a]
hptAllThings extract :: HomeModInfo -> [a]
extract hsc_env :: HscEnv
hsc_env = (HomeModInfo -> [a]) -> [HomeModInfo] -> [a]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap HomeModInfo -> [a]
extract (HomePackageTable -> [HomeModInfo]
eltsHpt (HscEnv -> HomePackageTable
hsc_HPT HscEnv
hsc_env))
hptSomeThingsBelowUs :: (HomeModInfo -> [a]) -> Bool -> HscEnv -> [(ModuleName, IsBootInterface)] -> [a]
hptSomeThingsBelowUs :: (HomeModInfo -> [a])
-> Bool -> HscEnv -> [(ModuleName, Bool)] -> [a]
hptSomeThingsBelowUs extract :: HomeModInfo -> [a]
extract include_hi_boot :: Bool
include_hi_boot hsc_env :: HscEnv
hsc_env deps :: [(ModuleName, Bool)]
deps
  | GhcMode -> Bool
isOneShot (DynFlags -> GhcMode
ghcMode (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)) = []
  | Bool
otherwise
  = let hpt :: HomePackageTable
hpt = HscEnv -> HomePackageTable
hsc_HPT HscEnv
hsc_env
    in
    [ a
thing
    |   
      (mod :: ModuleName
mod, is_boot_mod :: Bool
is_boot_mod) <- [(ModuleName, Bool)]
deps
    , Bool
include_hi_boot Bool -> Bool -> Bool
|| Bool -> Bool
not Bool
is_boot_mod
        
        
        
        
    , ModuleName
mod ModuleName -> ModuleName -> Bool
forall a. Eq a => a -> a -> Bool
/= Module -> ModuleName
moduleName Module
gHC_PRIM
        
    , let things :: [a]
things = case HomePackageTable -> ModuleName -> Maybe HomeModInfo
lookupHpt HomePackageTable
hpt ModuleName
mod of
                    Just info :: HomeModInfo
info -> HomeModInfo -> [a]
extract HomeModInfo
info
                    Nothing -> String -> SDoc -> [a] -> [a]
forall a. String -> SDoc -> a -> a
pprTrace "WARNING in hptSomeThingsBelowUs" SDoc
msg []
          msg :: SDoc
msg = [SDoc] -> SDoc
vcat [String -> SDoc
text "missing module" SDoc -> SDoc -> SDoc
<+> ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
mod,
                      String -> SDoc
text "Probable cause: out-of-date interface files"]
                        
        
    , a
thing <- [a]
things ]
data MetaRequest
  = MetaE  (LHsExpr GhcPs   -> MetaResult)
  | MetaP  (LPat GhcPs      -> MetaResult)
  | MetaT  (LHsType GhcPs   -> MetaResult)
  | MetaD  ([LHsDecl GhcPs] -> MetaResult)
  | MetaAW (Serialized     -> MetaResult)
data MetaResult
  = MetaResE  { MetaResult -> LHsExpr GhcPs
unMetaResE  :: LHsExpr GhcPs   }
  | MetaResP  { MetaResult -> LPat GhcPs
unMetaResP  :: LPat GhcPs      }
  | MetaResT  { MetaResult -> LHsType GhcPs
unMetaResT  :: LHsType GhcPs   }
  | MetaResD  { MetaResult -> [LHsDecl GhcPs]
unMetaResD  :: [LHsDecl GhcPs] }
  | MetaResAW { MetaResult -> Serialized
unMetaResAW :: Serialized        }
type MetaHook f = MetaRequest -> LHsExpr GhcTc -> f MetaResult
metaRequestE :: Functor f => MetaHook f -> LHsExpr GhcTc -> f (LHsExpr GhcPs)
metaRequestE :: MetaHook f -> LHsExpr GhcTc -> f (LHsExpr GhcPs)
metaRequestE h :: MetaHook f
h = (MetaResult -> LHsExpr GhcPs) -> f MetaResult -> f (LHsExpr GhcPs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MetaResult -> LHsExpr GhcPs
unMetaResE (f MetaResult -> f (LHsExpr GhcPs))
-> (LHsExpr GhcTc -> f MetaResult)
-> LHsExpr GhcTc
-> f (LHsExpr GhcPs)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MetaHook f
h ((LHsExpr GhcPs -> MetaResult) -> MetaRequest
MetaE LHsExpr GhcPs -> MetaResult
MetaResE)
metaRequestP :: Functor f => MetaHook f -> LHsExpr GhcTc -> f (LPat GhcPs)
metaRequestP :: MetaHook f -> LHsExpr GhcTc -> f (LPat GhcPs)
metaRequestP h :: MetaHook f
h = (MetaResult -> LPat GhcPs) -> f MetaResult -> f (LPat GhcPs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MetaResult -> LPat GhcPs
unMetaResP (f MetaResult -> f (LPat GhcPs))
-> (LHsExpr GhcTc -> f MetaResult)
-> LHsExpr GhcTc
-> f (LPat GhcPs)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MetaHook f
h ((LPat GhcPs -> MetaResult) -> MetaRequest
MetaP LPat GhcPs -> MetaResult
MetaResP)
metaRequestT :: Functor f => MetaHook f -> LHsExpr GhcTc -> f (LHsType GhcPs)
metaRequestT :: MetaHook f -> LHsExpr GhcTc -> f (LHsType GhcPs)
metaRequestT h :: MetaHook f
h = (MetaResult -> LHsType GhcPs) -> f MetaResult -> f (LHsType GhcPs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MetaResult -> LHsType GhcPs
unMetaResT (f MetaResult -> f (LHsType GhcPs))
-> (LHsExpr GhcTc -> f MetaResult)
-> LHsExpr GhcTc
-> f (LHsType GhcPs)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MetaHook f
h ((LHsType GhcPs -> MetaResult) -> MetaRequest
MetaT LHsType GhcPs -> MetaResult
MetaResT)
metaRequestD :: Functor f => MetaHook f -> LHsExpr GhcTc -> f [LHsDecl GhcPs]
metaRequestD :: MetaHook f -> LHsExpr GhcTc -> f [LHsDecl GhcPs]
metaRequestD h :: MetaHook f
h = (MetaResult -> [LHsDecl GhcPs])
-> f MetaResult -> f [LHsDecl GhcPs]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MetaResult -> [LHsDecl GhcPs]
unMetaResD (f MetaResult -> f [LHsDecl GhcPs])
-> (LHsExpr GhcTc -> f MetaResult)
-> LHsExpr GhcTc
-> f [LHsDecl GhcPs]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MetaHook f
h (([LHsDecl GhcPs] -> MetaResult) -> MetaRequest
MetaD [LHsDecl GhcPs] -> MetaResult
MetaResD)
metaRequestAW :: Functor f => MetaHook f -> LHsExpr GhcTc -> f Serialized
metaRequestAW :: MetaHook f -> LHsExpr GhcTc -> f Serialized
metaRequestAW h :: MetaHook f
h = (MetaResult -> Serialized) -> f MetaResult -> f Serialized
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MetaResult -> Serialized
unMetaResAW (f MetaResult -> f Serialized)
-> (LHsExpr GhcTc -> f MetaResult) -> LHsExpr GhcTc -> f Serialized
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MetaHook f
h ((Serialized -> MetaResult) -> MetaRequest
MetaAW Serialized -> MetaResult
MetaResAW)
prepareAnnotations :: HscEnv -> Maybe ModGuts -> IO AnnEnv
prepareAnnotations :: HscEnv -> Maybe ModGuts -> IO AnnEnv
prepareAnnotations hsc_env :: HscEnv
hsc_env mb_guts :: Maybe ModGuts
mb_guts = do
    ExternalPackageState
eps <- HscEnv -> IO ExternalPackageState
hscEPS HscEnv
hsc_env
    let 
        mb_this_module_anns :: Maybe AnnEnv
mb_this_module_anns = (ModGuts -> AnnEnv) -> Maybe ModGuts -> Maybe AnnEnv
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Annotation] -> AnnEnv
mkAnnEnv ([Annotation] -> AnnEnv)
-> (ModGuts -> [Annotation]) -> ModGuts -> AnnEnv
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModGuts -> [Annotation]
mg_anns) Maybe ModGuts
mb_guts
        
        
        
        home_pkg_anns :: AnnEnv
home_pkg_anns  = ([Annotation] -> AnnEnv
mkAnnEnv ([Annotation] -> AnnEnv)
-> (Maybe [(ModuleName, Bool)] -> [Annotation])
-> Maybe [(ModuleName, Bool)]
-> AnnEnv
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HscEnv -> Maybe [(ModuleName, Bool)] -> [Annotation]
hptAnns HscEnv
hsc_env) (Maybe [(ModuleName, Bool)] -> AnnEnv)
-> Maybe [(ModuleName, Bool)] -> AnnEnv
forall a b. (a -> b) -> a -> b
$ (ModGuts -> [(ModuleName, Bool)])
-> Maybe ModGuts -> Maybe [(ModuleName, Bool)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Dependencies -> [(ModuleName, Bool)]
dep_mods (Dependencies -> [(ModuleName, Bool)])
-> (ModGuts -> Dependencies) -> ModGuts -> [(ModuleName, Bool)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModGuts -> Dependencies
mg_deps) Maybe ModGuts
mb_guts
        other_pkg_anns :: AnnEnv
other_pkg_anns = ExternalPackageState -> AnnEnv
eps_ann_env ExternalPackageState
eps
        ann_env :: AnnEnv
ann_env        = (AnnEnv -> AnnEnv -> AnnEnv) -> [AnnEnv] -> AnnEnv
forall a. (a -> a -> a) -> [a] -> a
foldl1' AnnEnv -> AnnEnv -> AnnEnv
plusAnnEnv ([AnnEnv] -> AnnEnv) -> [AnnEnv] -> AnnEnv
forall a b. (a -> b) -> a -> b
$ [Maybe AnnEnv] -> [AnnEnv]
forall a. [Maybe a] -> [a]
catMaybes [Maybe AnnEnv
mb_this_module_anns,
                                                         AnnEnv -> Maybe AnnEnv
forall a. a -> Maybe a
Just AnnEnv
home_pkg_anns,
                                                         AnnEnv -> Maybe AnnEnv
forall a. a -> Maybe a
Just AnnEnv
other_pkg_anns]
    AnnEnv -> IO AnnEnv
forall (m :: * -> *) a. Monad m => a -> m a
return AnnEnv
ann_env
type FinderCache = InstalledModuleEnv InstalledFindResult
data InstalledFindResult
  = InstalledFound ModLocation InstalledModule
  | InstalledNoPackage InstalledUnitId
  | InstalledNotFound [FilePath] (Maybe InstalledUnitId)
data FindResult
  = Found ModLocation Module
        
  | NoPackage UnitId
        
  | FoundMultiple [(Module, ModuleOrigin)]
        
        
  | NotFound
      { FindResult -> [String]
fr_paths       :: [FilePath]       
      , FindResult -> Maybe UnitId
fr_pkg         :: Maybe UnitId  
                                           
                                           
      , FindResult -> [UnitId]
fr_mods_hidden :: [UnitId]      
                                           
      , FindResult -> [UnitId]
fr_pkgs_hidden :: [UnitId]      
                                           
        
      , FindResult -> [(UnitId, UnusablePackageReason)]
fr_unusables   :: [(UnitId, UnusablePackageReason)]
      , FindResult -> [ModuleSuggestion]
fr_suggestions :: [ModuleSuggestion] 
      }
data ModIface
  = ModIface {
        ModIface -> Module
mi_module     :: !Module,             
        ModIface -> Maybe Module
mi_sig_of     :: !(Maybe Module),     
        ModIface -> Fingerprint
mi_iface_hash :: !Fingerprint,        
        ModIface -> Fingerprint
mi_mod_hash   :: !Fingerprint,        
        ModIface -> Fingerprint
mi_flag_hash  :: !Fingerprint,        
                                              
                                              
        ModIface -> Fingerprint
mi_opt_hash   :: !Fingerprint,        
        ModIface -> Fingerprint
mi_hpc_hash   :: !Fingerprint,        
        ModIface -> Fingerprint
mi_plugin_hash :: !Fingerprint,       
        ModIface -> Bool
mi_orphan     :: !WhetherHasOrphans,  
        ModIface -> Bool
mi_finsts     :: !WhetherHasFamInst,
                
                
        ModIface -> HscSource
mi_hsc_src    :: !HscSource,          
        ModIface -> Dependencies
mi_deps     :: Dependencies,
                
                
                
        ModIface -> [Usage]
mi_usages   :: [Usage],
                
                
                
                
                
        ModIface -> [IfaceExport]
mi_exports  :: ![IfaceExport],
                
                
                
                
        ModIface -> Fingerprint
mi_exp_hash :: !Fingerprint,
                
        ModIface -> Bool
mi_used_th  :: !Bool,
                
                
        ModIface -> [(OccName, Fixity)]
mi_fixities :: [(OccName,Fixity)],
                
                
        ModIface -> Warnings
mi_warns    :: Warnings,
                
                
        ModIface -> [IfaceAnnotation]
mi_anns     :: [IfaceAnnotation],
                
                
        ModIface -> [(Fingerprint, IfaceDecl)]
mi_decls    :: [(Fingerprint,IfaceDecl)],
                
                
                
                
                
        ModIface -> Maybe GlobalRdrEnv
mi_globals  :: !(Maybe GlobalRdrEnv),
                
                
                
                
                
                
                
                
                
                
                
                
                
                
        ModIface -> [IfaceClsInst]
mi_insts       :: [IfaceClsInst],     
        ModIface -> [IfaceFamInst]
mi_fam_insts   :: [IfaceFamInst],  
        ModIface -> [IfaceRule]
mi_rules       :: [IfaceRule],     
        ModIface -> Fingerprint
mi_orphan_hash :: !Fingerprint,    
                                           
                
                
                
        ModIface -> OccName -> Maybe WarningTxt
mi_warn_fn   :: OccName -> Maybe WarningTxt,
                
        ModIface -> OccName -> Maybe Fixity
mi_fix_fn    :: OccName -> Maybe Fixity,
                
        ModIface -> OccName -> Maybe (OccName, Fingerprint)
mi_hash_fn   :: OccName -> Maybe (OccName, Fingerprint),
                
                
                
                
                
        ModIface -> Bool
mi_hpc       :: !AnyHpcUsage,
                
        ModIface -> IfaceTrustInfo
mi_trust     :: !IfaceTrustInfo,
                
        ModIface -> Bool
mi_trust_pkg :: !Bool,
                
                
                
                
                
                
        ModIface -> [IfaceCompleteMatch]
mi_complete_sigs :: [IfaceCompleteMatch],
        ModIface -> Maybe HsDocString
mi_doc_hdr :: Maybe HsDocString,
                
        ModIface -> DeclDocMap
mi_decl_docs :: DeclDocMap,
                
        ModIface -> ArgDocMap
mi_arg_docs :: ArgDocMap
                
     }
mi_boot :: ModIface -> Bool
mi_boot :: ModIface -> Bool
mi_boot iface :: ModIface
iface = ModIface -> HscSource
mi_hsc_src ModIface
iface HscSource -> HscSource -> Bool
forall a. Eq a => a -> a -> Bool
== HscSource
HsBootFile
mi_fix :: ModIface -> OccName -> Fixity
mi_fix :: ModIface -> OccName -> Fixity
mi_fix iface :: ModIface
iface name :: OccName
name = ModIface -> OccName -> Maybe Fixity
mi_fix_fn ModIface
iface OccName
name Maybe Fixity -> Fixity -> Fixity
forall a. Maybe a -> a -> a
`orElse` Fixity
defaultFixity
mi_semantic_module :: ModIface -> Module
mi_semantic_module :: ModIface -> Module
mi_semantic_module iface :: ModIface
iface = case ModIface -> Maybe Module
mi_sig_of ModIface
iface of
                            Nothing -> ModIface -> Module
mi_module ModIface
iface
                            Just mod :: Module
mod -> Module
mod
mi_free_holes :: ModIface -> UniqDSet ModuleName
mi_free_holes :: ModIface -> UniqDSet ModuleName
mi_free_holes iface :: ModIface
iface =
  case Module -> (InstalledModule, Maybe IndefModule)
splitModuleInsts (ModIface -> Module
mi_module ModIface
iface) of
    (_, Just indef :: IndefModule
indef)
        
        
        -> UniqDSet ModuleName
-> [(ModuleName, Module)] -> UniqDSet ModuleName
renameFreeHoles ([ModuleName] -> UniqDSet ModuleName
forall a. Uniquable a => [a] -> UniqDSet a
mkUniqDSet [ModuleName]
cands) (IndefUnitId -> [(ModuleName, Module)]
indefUnitIdInsts (IndefModule -> IndefUnitId
indefModuleUnitId IndefModule
indef))
    _   -> UniqDSet ModuleName
forall a. UniqDSet a
emptyUniqDSet
  where
    cands :: [ModuleName]
cands = ((ModuleName, Bool) -> ModuleName)
-> [(ModuleName, Bool)] -> [ModuleName]
forall a b. (a -> b) -> [a] -> [b]
map (ModuleName, Bool) -> ModuleName
forall a b. (a, b) -> a
fst (Dependencies -> [(ModuleName, Bool)]
dep_mods (ModIface -> Dependencies
mi_deps ModIface
iface))
renameFreeHoles :: UniqDSet ModuleName -> [(ModuleName, Module)] -> UniqDSet ModuleName
renameFreeHoles :: UniqDSet ModuleName
-> [(ModuleName, Module)] -> UniqDSet ModuleName
renameFreeHoles fhs :: UniqDSet ModuleName
fhs insts :: [(ModuleName, Module)]
insts =
    [UniqDSet ModuleName] -> UniqDSet ModuleName
forall a. [UniqDSet a] -> UniqDSet a
unionManyUniqDSets ((ModuleName -> UniqDSet ModuleName)
-> [ModuleName] -> [UniqDSet ModuleName]
forall a b. (a -> b) -> [a] -> [b]
map ModuleName -> UniqDSet ModuleName
forall key. Uniquable key => key -> UniqDSet ModuleName
lookup_impl (UniqDSet ModuleName -> [ModuleName]
forall a. UniqDSet a -> [a]
uniqDSetToList UniqDSet ModuleName
fhs))
  where
    hmap :: UniqFM Module
hmap = [(ModuleName, Module)] -> UniqFM Module
forall key elt. Uniquable key => [(key, elt)] -> UniqFM elt
listToUFM [(ModuleName, Module)]
insts
    lookup_impl :: key -> UniqDSet ModuleName
lookup_impl mod_name :: key
mod_name
        | Just mod :: Module
mod <- UniqFM Module -> key -> Maybe Module
forall key elt. Uniquable key => UniqFM elt -> key -> Maybe elt
lookupUFM UniqFM Module
hmap key
mod_name = Module -> UniqDSet ModuleName
moduleFreeHoles Module
mod
        
        | Bool
otherwise                           = UniqDSet ModuleName
forall a. UniqDSet a
emptyUniqDSet
instance Binary ModIface where
   put_ :: BinHandle -> ModIface -> IO ()
put_ bh :: BinHandle
bh (ModIface {
                 mi_module :: ModIface -> Module
mi_module    = Module
mod,
                 mi_sig_of :: ModIface -> Maybe Module
mi_sig_of    = Maybe Module
sig_of,
                 mi_hsc_src :: ModIface -> HscSource
mi_hsc_src   = HscSource
hsc_src,
                 mi_iface_hash :: ModIface -> Fingerprint
mi_iface_hash= Fingerprint
iface_hash,
                 mi_mod_hash :: ModIface -> Fingerprint
mi_mod_hash  = Fingerprint
mod_hash,
                 mi_flag_hash :: ModIface -> Fingerprint
mi_flag_hash = Fingerprint
flag_hash,
                 mi_opt_hash :: ModIface -> Fingerprint
mi_opt_hash  = Fingerprint
opt_hash,
                 mi_hpc_hash :: ModIface -> Fingerprint
mi_hpc_hash  = Fingerprint
hpc_hash,
                 mi_plugin_hash :: ModIface -> Fingerprint
mi_plugin_hash = Fingerprint
plugin_hash,
                 mi_orphan :: ModIface -> Bool
mi_orphan    = Bool
orphan,
                 mi_finsts :: ModIface -> Bool
mi_finsts    = Bool
hasFamInsts,
                 mi_deps :: ModIface -> Dependencies
mi_deps      = Dependencies
deps,
                 mi_usages :: ModIface -> [Usage]
mi_usages    = [Usage]
usages,
                 mi_exports :: ModIface -> [IfaceExport]
mi_exports   = [IfaceExport]
exports,
                 mi_exp_hash :: ModIface -> Fingerprint
mi_exp_hash  = Fingerprint
exp_hash,
                 mi_used_th :: ModIface -> Bool
mi_used_th   = Bool
used_th,
                 mi_fixities :: ModIface -> [(OccName, Fixity)]
mi_fixities  = [(OccName, Fixity)]
fixities,
                 mi_warns :: ModIface -> Warnings
mi_warns     = Warnings
warns,
                 mi_anns :: ModIface -> [IfaceAnnotation]
mi_anns      = [IfaceAnnotation]
anns,
                 mi_decls :: ModIface -> [(Fingerprint, IfaceDecl)]
mi_decls     = [(Fingerprint, IfaceDecl)]
decls,
                 mi_insts :: ModIface -> [IfaceClsInst]
mi_insts     = [IfaceClsInst]
insts,
                 mi_fam_insts :: ModIface -> [IfaceFamInst]
mi_fam_insts = [IfaceFamInst]
fam_insts,
                 mi_rules :: ModIface -> [IfaceRule]
mi_rules     = [IfaceRule]
rules,
                 mi_orphan_hash :: ModIface -> Fingerprint
mi_orphan_hash = Fingerprint
orphan_hash,
                 mi_hpc :: ModIface -> Bool
mi_hpc       = Bool
hpc_info,
                 mi_trust :: ModIface -> IfaceTrustInfo
mi_trust     = IfaceTrustInfo
trust,
                 mi_trust_pkg :: ModIface -> Bool
mi_trust_pkg = Bool
trust_pkg,
                 mi_complete_sigs :: ModIface -> [IfaceCompleteMatch]
mi_complete_sigs = [IfaceCompleteMatch]
complete_sigs,
                 mi_doc_hdr :: ModIface -> Maybe HsDocString
mi_doc_hdr   = Maybe HsDocString
doc_hdr,
                 mi_decl_docs :: ModIface -> DeclDocMap
mi_decl_docs = DeclDocMap
decl_docs,
                 mi_arg_docs :: ModIface -> ArgDocMap
mi_arg_docs  = ArgDocMap
arg_docs }) = do
        BinHandle -> Module -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Module
mod
        BinHandle -> Maybe Module -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Maybe Module
sig_of
        BinHandle -> HscSource -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh HscSource
hsc_src
        BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Fingerprint
iface_hash
        BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Fingerprint
mod_hash
        BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Fingerprint
flag_hash
        BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Fingerprint
opt_hash
        BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Fingerprint
hpc_hash
        BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Fingerprint
plugin_hash
        BinHandle -> Bool -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Bool
orphan
        BinHandle -> Bool -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Bool
hasFamInsts
        BinHandle -> Dependencies -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
lazyPut BinHandle
bh Dependencies
deps
        BinHandle -> [Usage] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
lazyPut BinHandle
bh [Usage]
usages
        BinHandle -> [IfaceExport] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [IfaceExport]
exports
        BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Fingerprint
exp_hash
        BinHandle -> Bool -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Bool
used_th
        BinHandle -> [(OccName, Fixity)] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [(OccName, Fixity)]
fixities
        BinHandle -> Warnings -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
lazyPut BinHandle
bh Warnings
warns
        BinHandle -> [IfaceAnnotation] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
lazyPut BinHandle
bh [IfaceAnnotation]
anns
        BinHandle -> [(Fingerprint, IfaceDecl)] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [(Fingerprint, IfaceDecl)]
decls
        BinHandle -> [IfaceClsInst] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [IfaceClsInst]
insts
        BinHandle -> [IfaceFamInst] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [IfaceFamInst]
fam_insts
        BinHandle -> [IfaceRule] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
lazyPut BinHandle
bh [IfaceRule]
rules
        BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Fingerprint
orphan_hash
        BinHandle -> Bool -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Bool
hpc_info
        BinHandle -> IfaceTrustInfo -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh IfaceTrustInfo
trust
        BinHandle -> Bool -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Bool
trust_pkg
        BinHandle -> [IfaceCompleteMatch] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [IfaceCompleteMatch]
complete_sigs
        BinHandle -> Maybe HsDocString -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
lazyPut BinHandle
bh Maybe HsDocString
doc_hdr
        BinHandle -> DeclDocMap -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
lazyPut BinHandle
bh DeclDocMap
decl_docs
        BinHandle -> ArgDocMap -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
lazyPut BinHandle
bh ArgDocMap
arg_docs
   get :: BinHandle -> IO ModIface
get bh :: BinHandle
bh = do
        Module
mod         <- BinHandle -> IO Module
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        Maybe Module
sig_of      <- BinHandle -> IO (Maybe Module)
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        HscSource
hsc_src     <- BinHandle -> IO HscSource
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        Fingerprint
iface_hash  <- BinHandle -> IO Fingerprint
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        Fingerprint
mod_hash    <- BinHandle -> IO Fingerprint
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        Fingerprint
flag_hash   <- BinHandle -> IO Fingerprint
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        Fingerprint
opt_hash    <- BinHandle -> IO Fingerprint
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        Fingerprint
hpc_hash    <- BinHandle -> IO Fingerprint
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        Fingerprint
plugin_hash <- BinHandle -> IO Fingerprint
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        Bool
orphan      <- BinHandle -> IO Bool
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        Bool
hasFamInsts <- BinHandle -> IO Bool
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        Dependencies
deps        <- BinHandle -> IO Dependencies
forall a. Binary a => BinHandle -> IO a
lazyGet BinHandle
bh
        [Usage]
usages      <- {-# SCC "bin_usages" #-} BinHandle -> IO [Usage]
forall a. Binary a => BinHandle -> IO a
lazyGet BinHandle
bh
        [IfaceExport]
exports     <- {-# SCC "bin_exports" #-} BinHandle -> IO [IfaceExport]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        Fingerprint
exp_hash    <- BinHandle -> IO Fingerprint
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        Bool
used_th     <- BinHandle -> IO Bool
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        [(OccName, Fixity)]
fixities    <- {-# SCC "bin_fixities" #-} BinHandle -> IO [(OccName, Fixity)]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        Warnings
warns       <- {-# SCC "bin_warns" #-} BinHandle -> IO Warnings
forall a. Binary a => BinHandle -> IO a
lazyGet BinHandle
bh
        [IfaceAnnotation]
anns        <- {-# SCC "bin_anns" #-} BinHandle -> IO [IfaceAnnotation]
forall a. Binary a => BinHandle -> IO a
lazyGet BinHandle
bh
        [(Fingerprint, IfaceDecl)]
decls       <- {-# SCC "bin_tycldecls" #-} BinHandle -> IO [(Fingerprint, IfaceDecl)]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        [IfaceClsInst]
insts       <- {-# SCC "bin_insts" #-} BinHandle -> IO [IfaceClsInst]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        [IfaceFamInst]
fam_insts   <- {-# SCC "bin_fam_insts" #-} BinHandle -> IO [IfaceFamInst]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        [IfaceRule]
rules       <- {-# SCC "bin_rules" #-} BinHandle -> IO [IfaceRule]
forall a. Binary a => BinHandle -> IO a
lazyGet BinHandle
bh
        Fingerprint
orphan_hash <- BinHandle -> IO Fingerprint
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        Bool
hpc_info    <- BinHandle -> IO Bool
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        IfaceTrustInfo
trust       <- BinHandle -> IO IfaceTrustInfo
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        Bool
trust_pkg   <- BinHandle -> IO Bool
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        [IfaceCompleteMatch]
complete_sigs <- BinHandle -> IO [IfaceCompleteMatch]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        Maybe HsDocString
doc_hdr     <- BinHandle -> IO (Maybe HsDocString)
forall a. Binary a => BinHandle -> IO a
lazyGet BinHandle
bh
        DeclDocMap
decl_docs   <- BinHandle -> IO DeclDocMap
forall a. Binary a => BinHandle -> IO a
lazyGet BinHandle
bh
        ArgDocMap
arg_docs    <- BinHandle -> IO ArgDocMap
forall a. Binary a => BinHandle -> IO a
lazyGet BinHandle
bh
        ModIface -> IO ModIface
forall (m :: * -> *) a. Monad m => a -> m a
return ($WModIface :: Module
-> Maybe Module
-> Fingerprint
-> Fingerprint
-> Fingerprint
-> Fingerprint
-> Fingerprint
-> Fingerprint
-> Bool
-> Bool
-> HscSource
-> Dependencies
-> [Usage]
-> [IfaceExport]
-> Fingerprint
-> Bool
-> [(OccName, Fixity)]
-> Warnings
-> [IfaceAnnotation]
-> [(Fingerprint, IfaceDecl)]
-> Maybe GlobalRdrEnv
-> [IfaceClsInst]
-> [IfaceFamInst]
-> [IfaceRule]
-> Fingerprint
-> (OccName -> Maybe WarningTxt)
-> (OccName -> Maybe Fixity)
-> (OccName -> Maybe (OccName, Fingerprint))
-> Bool
-> IfaceTrustInfo
-> Bool
-> [IfaceCompleteMatch]
-> Maybe HsDocString
-> DeclDocMap
-> ArgDocMap
-> ModIface
ModIface {
                 mi_module :: Module
mi_module      = Module
mod,
                 mi_sig_of :: Maybe Module
mi_sig_of      = Maybe Module
sig_of,
                 mi_hsc_src :: HscSource
mi_hsc_src     = HscSource
hsc_src,
                 mi_iface_hash :: Fingerprint
mi_iface_hash  = Fingerprint
iface_hash,
                 mi_mod_hash :: Fingerprint
mi_mod_hash    = Fingerprint
mod_hash,
                 mi_flag_hash :: Fingerprint
mi_flag_hash   = Fingerprint
flag_hash,
                 mi_opt_hash :: Fingerprint
mi_opt_hash    = Fingerprint
opt_hash,
                 mi_hpc_hash :: Fingerprint
mi_hpc_hash    = Fingerprint
hpc_hash,
                 mi_plugin_hash :: Fingerprint
mi_plugin_hash = Fingerprint
plugin_hash,
                 mi_orphan :: Bool
mi_orphan      = Bool
orphan,
                 mi_finsts :: Bool
mi_finsts      = Bool
hasFamInsts,
                 mi_deps :: Dependencies
mi_deps        = Dependencies
deps,
                 mi_usages :: [Usage]
mi_usages      = [Usage]
usages,
                 mi_exports :: [IfaceExport]
mi_exports     = [IfaceExport]
exports,
                 mi_exp_hash :: Fingerprint
mi_exp_hash    = Fingerprint
exp_hash,
                 mi_used_th :: Bool
mi_used_th     = Bool
used_th,
                 mi_anns :: [IfaceAnnotation]
mi_anns        = [IfaceAnnotation]
anns,
                 mi_fixities :: [(OccName, Fixity)]
mi_fixities    = [(OccName, Fixity)]
fixities,
                 mi_warns :: Warnings
mi_warns       = Warnings
warns,
                 mi_decls :: [(Fingerprint, IfaceDecl)]
mi_decls       = [(Fingerprint, IfaceDecl)]
decls,
                 mi_globals :: Maybe GlobalRdrEnv
mi_globals     = Maybe GlobalRdrEnv
forall a. Maybe a
Nothing,
                 mi_insts :: [IfaceClsInst]
mi_insts       = [IfaceClsInst]
insts,
                 mi_fam_insts :: [IfaceFamInst]
mi_fam_insts   = [IfaceFamInst]
fam_insts,
                 mi_rules :: [IfaceRule]
mi_rules       = [IfaceRule]
rules,
                 mi_orphan_hash :: Fingerprint
mi_orphan_hash = Fingerprint
orphan_hash,
                 mi_hpc :: Bool
mi_hpc         = Bool
hpc_info,
                 mi_trust :: IfaceTrustInfo
mi_trust       = IfaceTrustInfo
trust,
                 mi_trust_pkg :: Bool
mi_trust_pkg   = Bool
trust_pkg,
                        
                 mi_warn_fn :: OccName -> Maybe WarningTxt
mi_warn_fn     = Warnings -> OccName -> Maybe WarningTxt
mkIfaceWarnCache Warnings
warns,
                 mi_fix_fn :: OccName -> Maybe Fixity
mi_fix_fn      = [(OccName, Fixity)] -> OccName -> Maybe Fixity
mkIfaceFixCache [(OccName, Fixity)]
fixities,
                 mi_hash_fn :: OccName -> Maybe (OccName, Fingerprint)
mi_hash_fn     = [(Fingerprint, IfaceDecl)]
-> OccName -> Maybe (OccName, Fingerprint)
mkIfaceHashCache [(Fingerprint, IfaceDecl)]
decls,
                 mi_complete_sigs :: [IfaceCompleteMatch]
mi_complete_sigs = [IfaceCompleteMatch]
complete_sigs,
                 mi_doc_hdr :: Maybe HsDocString
mi_doc_hdr     = Maybe HsDocString
doc_hdr,
                 mi_decl_docs :: DeclDocMap
mi_decl_docs   = DeclDocMap
decl_docs,
                 mi_arg_docs :: ArgDocMap
mi_arg_docs    = ArgDocMap
arg_docs })
type IfaceExport = AvailInfo
emptyModIface :: Module -> ModIface
emptyModIface :: Module -> ModIface
emptyModIface mod :: Module
mod
  = $WModIface :: Module
-> Maybe Module
-> Fingerprint
-> Fingerprint
-> Fingerprint
-> Fingerprint
-> Fingerprint
-> Fingerprint
-> Bool
-> Bool
-> HscSource
-> Dependencies
-> [Usage]
-> [IfaceExport]
-> Fingerprint
-> Bool
-> [(OccName, Fixity)]
-> Warnings
-> [IfaceAnnotation]
-> [(Fingerprint, IfaceDecl)]
-> Maybe GlobalRdrEnv
-> [IfaceClsInst]
-> [IfaceFamInst]
-> [IfaceRule]
-> Fingerprint
-> (OccName -> Maybe WarningTxt)
-> (OccName -> Maybe Fixity)
-> (OccName -> Maybe (OccName, Fingerprint))
-> Bool
-> IfaceTrustInfo
-> Bool
-> [IfaceCompleteMatch]
-> Maybe HsDocString
-> DeclDocMap
-> ArgDocMap
-> ModIface
ModIface { mi_module :: Module
mi_module      = Module
mod,
               mi_sig_of :: Maybe Module
mi_sig_of      = Maybe Module
forall a. Maybe a
Nothing,
               mi_iface_hash :: Fingerprint
mi_iface_hash  = Fingerprint
fingerprint0,
               mi_mod_hash :: Fingerprint
mi_mod_hash    = Fingerprint
fingerprint0,
               mi_flag_hash :: Fingerprint
mi_flag_hash   = Fingerprint
fingerprint0,
               mi_opt_hash :: Fingerprint
mi_opt_hash    = Fingerprint
fingerprint0,
               mi_hpc_hash :: Fingerprint
mi_hpc_hash    = Fingerprint
fingerprint0,
               mi_plugin_hash :: Fingerprint
mi_plugin_hash = Fingerprint
fingerprint0,
               mi_orphan :: Bool
mi_orphan      = Bool
False,
               mi_finsts :: Bool
mi_finsts      = Bool
False,
               mi_hsc_src :: HscSource
mi_hsc_src     = HscSource
HsSrcFile,
               mi_deps :: Dependencies
mi_deps        = Dependencies
noDependencies,
               mi_usages :: [Usage]
mi_usages      = [],
               mi_exports :: [IfaceExport]
mi_exports     = [],
               mi_exp_hash :: Fingerprint
mi_exp_hash    = Fingerprint
fingerprint0,
               mi_used_th :: Bool
mi_used_th     = Bool
False,
               mi_fixities :: [(OccName, Fixity)]
mi_fixities    = [],
               mi_warns :: Warnings
mi_warns       = Warnings
NoWarnings,
               mi_anns :: [IfaceAnnotation]
mi_anns        = [],
               mi_insts :: [IfaceClsInst]
mi_insts       = [],
               mi_fam_insts :: [IfaceFamInst]
mi_fam_insts   = [],
               mi_rules :: [IfaceRule]
mi_rules       = [],
               mi_decls :: [(Fingerprint, IfaceDecl)]
mi_decls       = [],
               mi_globals :: Maybe GlobalRdrEnv
mi_globals     = Maybe GlobalRdrEnv
forall a. Maybe a
Nothing,
               mi_orphan_hash :: Fingerprint
mi_orphan_hash = Fingerprint
fingerprint0,
               mi_warn_fn :: OccName -> Maybe WarningTxt
mi_warn_fn     = OccName -> Maybe WarningTxt
emptyIfaceWarnCache,
               mi_fix_fn :: OccName -> Maybe Fixity
mi_fix_fn      = OccName -> Maybe Fixity
emptyIfaceFixCache,
               mi_hash_fn :: OccName -> Maybe (OccName, Fingerprint)
mi_hash_fn     = OccName -> Maybe (OccName, Fingerprint)
emptyIfaceHashCache,
               mi_hpc :: Bool
mi_hpc         = Bool
False,
               mi_trust :: IfaceTrustInfo
mi_trust       = IfaceTrustInfo
noIfaceTrustInfo,
               mi_trust_pkg :: Bool
mi_trust_pkg   = Bool
False,
               mi_complete_sigs :: [IfaceCompleteMatch]
mi_complete_sigs = [],
               mi_doc_hdr :: Maybe HsDocString
mi_doc_hdr     = Maybe HsDocString
forall a. Maybe a
Nothing,
               mi_decl_docs :: DeclDocMap
mi_decl_docs   = DeclDocMap
emptyDeclDocMap,
               mi_arg_docs :: ArgDocMap
mi_arg_docs    = ArgDocMap
emptyArgDocMap }
mkIfaceHashCache :: [(Fingerprint,IfaceDecl)]
                 -> (OccName -> Maybe (OccName, Fingerprint))
mkIfaceHashCache :: [(Fingerprint, IfaceDecl)]
-> OccName -> Maybe (OccName, Fingerprint)
mkIfaceHashCache pairs :: [(Fingerprint, IfaceDecl)]
pairs
  = \occ :: OccName
occ -> OccEnv (OccName, Fingerprint)
-> OccName -> Maybe (OccName, Fingerprint)
forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv OccEnv (OccName, Fingerprint)
env OccName
occ
  where
    env :: OccEnv (OccName, Fingerprint)
env = (OccEnv (OccName, Fingerprint)
 -> (Fingerprint, IfaceDecl) -> OccEnv (OccName, Fingerprint))
-> OccEnv (OccName, Fingerprint)
-> [(Fingerprint, IfaceDecl)]
-> OccEnv (OccName, Fingerprint)
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' OccEnv (OccName, Fingerprint)
-> (Fingerprint, IfaceDecl) -> OccEnv (OccName, Fingerprint)
add_decl OccEnv (OccName, Fingerprint)
forall a. OccEnv a
emptyOccEnv [(Fingerprint, IfaceDecl)]
pairs
    add_decl :: OccEnv (OccName, Fingerprint)
-> (Fingerprint, IfaceDecl) -> OccEnv (OccName, Fingerprint)
add_decl env0 :: OccEnv (OccName, Fingerprint)
env0 (v :: Fingerprint
v,d :: IfaceDecl
d) = (OccEnv (OccName, Fingerprint)
 -> (OccName, Fingerprint) -> OccEnv (OccName, Fingerprint))
-> OccEnv (OccName, Fingerprint)
-> [(OccName, Fingerprint)]
-> OccEnv (OccName, Fingerprint)
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' OccEnv (OccName, Fingerprint)
-> (OccName, Fingerprint) -> OccEnv (OccName, Fingerprint)
forall b.
OccEnv (OccName, b) -> (OccName, b) -> OccEnv (OccName, b)
add OccEnv (OccName, Fingerprint)
env0 (Fingerprint -> IfaceDecl -> [(OccName, Fingerprint)]
ifaceDeclFingerprints Fingerprint
v IfaceDecl
d)
      where
        add :: OccEnv (OccName, b) -> (OccName, b) -> OccEnv (OccName, b)
add env0 :: OccEnv (OccName, b)
env0 (occ :: OccName
occ,hash :: b
hash) = OccEnv (OccName, b)
-> OccName -> (OccName, b) -> OccEnv (OccName, b)
forall a. OccEnv a -> OccName -> a -> OccEnv a
extendOccEnv OccEnv (OccName, b)
env0 OccName
occ (OccName
occ,b
hash)
emptyIfaceHashCache :: OccName -> Maybe (OccName, Fingerprint)
emptyIfaceHashCache :: OccName -> Maybe (OccName, Fingerprint)
emptyIfaceHashCache _occ :: OccName
_occ = Maybe (OccName, Fingerprint)
forall a. Maybe a
Nothing
data ModDetails
  = ModDetails {
        
        ModDetails -> [IfaceExport]
md_exports   :: [AvailInfo],
        ModDetails -> TypeEnv
md_types     :: !TypeEnv,       
                                        
        ModDetails -> [ClsInst]
md_insts     :: ![ClsInst],     
        ModDetails -> [FamInst]
md_fam_insts :: ![FamInst],
        ModDetails -> [CoreRule]
md_rules     :: ![CoreRule],    
        ModDetails -> [Annotation]
md_anns      :: ![Annotation],  
                                        
        ModDetails -> [CompleteMatch]
md_complete_sigs :: [CompleteMatch]
          
     }
emptyModDetails :: ModDetails
emptyModDetails :: ModDetails
emptyModDetails
  = $WModDetails :: [IfaceExport]
-> TypeEnv
-> [ClsInst]
-> [FamInst]
-> [CoreRule]
-> [Annotation]
-> [CompleteMatch]
-> ModDetails
ModDetails { md_types :: TypeEnv
md_types     = TypeEnv
emptyTypeEnv,
                 md_exports :: [IfaceExport]
md_exports   = [],
                 md_insts :: [ClsInst]
md_insts     = [],
                 md_rules :: [CoreRule]
md_rules     = [],
                 md_fam_insts :: [FamInst]
md_fam_insts = [],
                 md_anns :: [Annotation]
md_anns      = [],
                 md_complete_sigs :: [CompleteMatch]
md_complete_sigs = [] }
type ImportedMods = ModuleEnv [ImportedBy]
data ImportedBy
    = ImportedByUser ImportedModsVal
    | ImportedBySystem
importedByUser :: [ImportedBy] -> [ImportedModsVal]
importedByUser :: [ImportedBy] -> [ImportedModsVal]
importedByUser (ImportedByUser imv :: ImportedModsVal
imv : bys :: [ImportedBy]
bys) = ImportedModsVal
imv ImportedModsVal -> [ImportedModsVal] -> [ImportedModsVal]
forall a. a -> [a] -> [a]
: [ImportedBy] -> [ImportedModsVal]
importedByUser [ImportedBy]
bys
importedByUser (ImportedBySystem   : bys :: [ImportedBy]
bys) =       [ImportedBy] -> [ImportedModsVal]
importedByUser [ImportedBy]
bys
importedByUser [] = []
data ImportedModsVal
 = ImportedModsVal {
        ImportedModsVal -> ModuleName
imv_name :: ModuleName,          
        ImportedModsVal -> SrcSpan
imv_span :: SrcSpan,             
        ImportedModsVal -> Bool
imv_is_safe :: IsSafeImport,     
        ImportedModsVal -> Bool
imv_is_hiding :: Bool,           
        ImportedModsVal -> GlobalRdrEnv
imv_all_exports :: !GlobalRdrEnv, 
          
        ImportedModsVal -> Bool
imv_qualified :: Bool            
        }
data ModGuts
  = ModGuts {
        ModGuts -> Module
mg_module    :: !Module,         
        ModGuts -> HscSource
mg_hsc_src   :: HscSource,       
        ModGuts -> SrcSpan
mg_loc       :: SrcSpan,         
        ModGuts -> [IfaceExport]
mg_exports   :: ![AvailInfo],    
        ModGuts -> Dependencies
mg_deps      :: !Dependencies,   
                                         
        ModGuts -> [Usage]
mg_usages    :: ![Usage],        
        ModGuts -> Bool
mg_used_th   :: !Bool,           
        ModGuts -> GlobalRdrEnv
mg_rdr_env   :: !GlobalRdrEnv,   
        
        ModGuts -> FixityEnv
mg_fix_env   :: !FixityEnv,      
                                         
        ModGuts -> [TyCon]
mg_tcs       :: ![TyCon],        
                                         
        ModGuts -> [ClsInst]
mg_insts     :: ![ClsInst],      
        ModGuts -> [FamInst]
mg_fam_insts :: ![FamInst],
                                         
        ModGuts -> [PatSyn]
mg_patsyns   :: ![PatSyn],       
        ModGuts -> [CoreRule]
mg_rules     :: ![CoreRule],     
                                         
        ModGuts -> CoreProgram
mg_binds     :: !CoreProgram,    
        ModGuts -> ForeignStubs
mg_foreign   :: !ForeignStubs,   
        ModGuts -> [(ForeignSrcLang, String)]
mg_foreign_files :: ![(ForeignSrcLang, FilePath)],
        
        ModGuts -> Warnings
mg_warns     :: !Warnings,       
        ModGuts -> [Annotation]
mg_anns      :: [Annotation],    
        ModGuts -> [CompleteMatch]
mg_complete_sigs :: [CompleteMatch], 
        ModGuts -> HpcInfo
mg_hpc_info  :: !HpcInfo,        
        ModGuts -> Maybe ModBreaks
mg_modBreaks :: !(Maybe ModBreaks), 
                        
                        
                        
                        
                        
        ModGuts -> InstEnv
mg_inst_env     :: InstEnv,             
                                                
                                                
        ModGuts -> FamInstEnv
mg_fam_inst_env :: FamInstEnv,          
                                                
                                                
        ModGuts -> SafeHaskellMode
mg_safe_haskell :: SafeHaskellMode,     
        ModGuts -> Bool
mg_trust_pkg    :: Bool,                
                                                
                                                
        ModGuts -> Maybe HsDocString
mg_doc_hdr       :: !(Maybe HsDocString), 
        ModGuts -> DeclDocMap
mg_decl_docs     :: !DeclDocMap,     
        ModGuts -> ArgDocMap
mg_arg_docs      :: !ArgDocMap       
    }
data CgGuts
  = CgGuts {
        CgGuts -> Module
cg_module    :: !Module,
                
        CgGuts -> [TyCon]
cg_tycons    :: [TyCon],
                
                
                
                
        CgGuts -> CoreProgram
cg_binds     :: CoreProgram,
                
                
                
                
                
        CgGuts -> ForeignStubs
cg_foreign   :: !ForeignStubs,   
        CgGuts -> [(ForeignSrcLang, String)]
cg_foreign_files :: ![(ForeignSrcLang, FilePath)],
        CgGuts -> [InstalledUnitId]
cg_dep_pkgs  :: ![InstalledUnitId], 
                                            
        CgGuts -> HpcInfo
cg_hpc_info  :: !HpcInfo,           
        CgGuts -> Maybe ModBreaks
cg_modBreaks :: !(Maybe ModBreaks), 
        CgGuts -> [SptEntry]
cg_spt_entries :: [SptEntry]
                
                
                
    }
data ForeignStubs
  = NoStubs
      
  | ForeignStubs SDoc SDoc
      
      
      
      
      
      
      
appendStubC :: ForeignStubs -> SDoc -> ForeignStubs
appendStubC :: ForeignStubs -> SDoc -> ForeignStubs
appendStubC NoStubs            c_code :: SDoc
c_code = SDoc -> SDoc -> ForeignStubs
ForeignStubs SDoc
empty SDoc
c_code
appendStubC (ForeignStubs h :: SDoc
h c :: SDoc
c) c_code :: SDoc
c_code = SDoc -> SDoc -> ForeignStubs
ForeignStubs SDoc
h (SDoc
c SDoc -> SDoc -> SDoc
$$ SDoc
c_code)
data SptEntry = SptEntry Id Fingerprint
instance Outputable SptEntry where
  ppr :: SptEntry -> SDoc
ppr (SptEntry id :: Id
id fpr :: Fingerprint
fpr) = Id -> SDoc
forall a. Outputable a => a -> SDoc
ppr Id
id SDoc -> SDoc -> SDoc
<> SDoc
colon SDoc -> SDoc -> SDoc
<+> Fingerprint -> SDoc
forall a. Outputable a => a -> SDoc
ppr Fingerprint
fpr
data InteractiveContext
  = InteractiveContext {
         InteractiveContext -> DynFlags
ic_dflags     :: DynFlags,
             
             
         InteractiveContext -> Int
ic_mod_index :: Int,
             
             
             
             
             
         InteractiveContext -> [InteractiveImport]
ic_imports :: [InteractiveImport],
             
             
             
             
             
             
             
         InteractiveContext -> [TyThing]
ic_tythings   :: [TyThing],
             
             
             
         InteractiveContext -> GlobalRdrEnv
ic_rn_gbl_env :: GlobalRdrEnv,
             
             
             
             
         InteractiveContext -> ([ClsInst], [FamInst])
ic_instances  :: ([ClsInst], [FamInst]),
             
             
             
             
             
             
         InteractiveContext -> FixityEnv
ic_fix_env :: FixityEnv,
            
         InteractiveContext -> Maybe [Type]
ic_default :: Maybe [Type],
             
          InteractiveContext -> [Resume]
ic_resume :: [Resume],
             
         InteractiveContext -> Name
ic_monad      :: Name,
             
         InteractiveContext -> Name
ic_int_print  :: Name,
             
             
         InteractiveContext -> Maybe String
ic_cwd :: Maybe FilePath
             
    }
data InteractiveImport
  = IIDecl (ImportDecl GhcPs)
      
      
  | IIModule ModuleName
      
      
      
emptyInteractiveContext :: DynFlags -> InteractiveContext
emptyInteractiveContext :: DynFlags -> InteractiveContext
emptyInteractiveContext dflags :: DynFlags
dflags
  = InteractiveContext :: DynFlags
-> Int
-> [InteractiveImport]
-> [TyThing]
-> GlobalRdrEnv
-> ([ClsInst], [FamInst])
-> FixityEnv
-> Maybe [Type]
-> [Resume]
-> Name
-> Name
-> Maybe String
-> InteractiveContext
InteractiveContext {
       ic_dflags :: DynFlags
ic_dflags     = DynFlags
dflags,
       ic_imports :: [InteractiveImport]
ic_imports    = [],
       ic_rn_gbl_env :: GlobalRdrEnv
ic_rn_gbl_env = GlobalRdrEnv
emptyGlobalRdrEnv,
       ic_mod_index :: Int
ic_mod_index  = 1,
       ic_tythings :: [TyThing]
ic_tythings   = [],
       ic_instances :: ([ClsInst], [FamInst])
ic_instances  = ([],[]),
       ic_fix_env :: FixityEnv
ic_fix_env    = FixityEnv
forall a. NameEnv a
emptyNameEnv,
       ic_monad :: Name
ic_monad      = Name
ioTyConName,  
       ic_int_print :: Name
ic_int_print  = Name
printName,    
       ic_default :: Maybe [Type]
ic_default    = Maybe [Type]
forall a. Maybe a
Nothing,
       ic_resume :: [Resume]
ic_resume     = [],
       ic_cwd :: Maybe String
ic_cwd        = Maybe String
forall a. Maybe a
Nothing }
icInteractiveModule :: InteractiveContext -> Module
icInteractiveModule :: InteractiveContext -> Module
icInteractiveModule (InteractiveContext { ic_mod_index :: InteractiveContext -> Int
ic_mod_index = Int
index })
  = Int -> Module
mkInteractiveModule Int
index
icInScopeTTs :: InteractiveContext -> [TyThing]
icInScopeTTs :: InteractiveContext -> [TyThing]
icInScopeTTs = InteractiveContext -> [TyThing]
ic_tythings
icPrintUnqual :: DynFlags -> InteractiveContext -> PrintUnqualified
icPrintUnqual :: DynFlags -> InteractiveContext -> PrintUnqualified
icPrintUnqual dflags :: DynFlags
dflags InteractiveContext{ ic_rn_gbl_env :: InteractiveContext -> GlobalRdrEnv
ic_rn_gbl_env = GlobalRdrEnv
grenv } =
    DynFlags -> GlobalRdrEnv -> PrintUnqualified
mkPrintUnqualified DynFlags
dflags GlobalRdrEnv
grenv
extendInteractiveContext :: InteractiveContext
                         -> [TyThing]
                         -> [ClsInst] -> [FamInst]
                         -> Maybe [Type]
                         -> FixityEnv
                         -> InteractiveContext
extendInteractiveContext :: InteractiveContext
-> [TyThing]
-> [ClsInst]
-> [FamInst]
-> Maybe [Type]
-> FixityEnv
-> InteractiveContext
extendInteractiveContext ictxt :: InteractiveContext
ictxt new_tythings :: [TyThing]
new_tythings new_cls_insts :: [ClsInst]
new_cls_insts new_fam_insts :: [FamInst]
new_fam_insts defaults :: Maybe [Type]
defaults fix_env :: FixityEnv
fix_env
  = InteractiveContext
ictxt { ic_mod_index :: Int
ic_mod_index  = InteractiveContext -> Int
ic_mod_index InteractiveContext
ictxt Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 1
                            
                            
          , ic_tythings :: [TyThing]
ic_tythings   = [TyThing]
new_tythings [TyThing] -> [TyThing] -> [TyThing]
forall a. [a] -> [a] -> [a]
++ [TyThing]
old_tythings
          , ic_rn_gbl_env :: GlobalRdrEnv
ic_rn_gbl_env = InteractiveContext -> GlobalRdrEnv
ic_rn_gbl_env InteractiveContext
ictxt GlobalRdrEnv -> [TyThing] -> GlobalRdrEnv
`icExtendGblRdrEnv` [TyThing]
new_tythings
          , ic_instances :: ([ClsInst], [FamInst])
ic_instances  = ( [ClsInst]
new_cls_insts [ClsInst] -> [ClsInst] -> [ClsInst]
forall a. [a] -> [a] -> [a]
++ [ClsInst]
old_cls_insts
                            , [FamInst]
new_fam_insts [FamInst] -> [FamInst] -> [FamInst]
forall a. [a] -> [a] -> [a]
++ [FamInst]
fam_insts )
                            
                            
          , ic_default :: Maybe [Type]
ic_default    = Maybe [Type]
defaults
          , ic_fix_env :: FixityEnv
ic_fix_env    = FixityEnv
fix_env  
          }
  where
    new_ids :: [Id]
new_ids = [Id
id | AnId id :: Id
id <- [TyThing]
new_tythings]
    old_tythings :: [TyThing]
old_tythings = (TyThing -> Bool) -> [TyThing] -> [TyThing]
forall a. (a -> Bool) -> [a] -> [a]
filterOut ([Id] -> TyThing -> Bool
shadowed_by [Id]
new_ids) (InteractiveContext -> [TyThing]
ic_tythings InteractiveContext
ictxt)
    
    
    (cls_insts :: [ClsInst]
cls_insts, fam_insts :: [FamInst]
fam_insts) = InteractiveContext -> ([ClsInst], [FamInst])
ic_instances InteractiveContext
ictxt
    old_cls_insts :: [ClsInst]
old_cls_insts = (ClsInst -> Bool) -> [ClsInst] -> [ClsInst]
forall a. (a -> Bool) -> [a] -> [a]
filterOut (\i :: ClsInst
i -> (ClsInst -> Bool) -> [ClsInst] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (ClsInst -> ClsInst -> Bool
identicalClsInstHead ClsInst
i) [ClsInst]
new_cls_insts) [ClsInst]
cls_insts
extendInteractiveContextWithIds :: InteractiveContext -> [Id] -> InteractiveContext
extendInteractiveContextWithIds :: InteractiveContext -> [Id] -> InteractiveContext
extendInteractiveContextWithIds ictxt :: InteractiveContext
ictxt new_ids :: [Id]
new_ids
  | [Id] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Id]
new_ids = InteractiveContext
ictxt
  | Bool
otherwise    = InteractiveContext
ictxt { ic_mod_index :: Int
ic_mod_index  = InteractiveContext -> Int
ic_mod_index InteractiveContext
ictxt Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 1
                         , ic_tythings :: [TyThing]
ic_tythings   = [TyThing]
new_tythings [TyThing] -> [TyThing] -> [TyThing]
forall a. [a] -> [a] -> [a]
++ [TyThing]
old_tythings
                         , ic_rn_gbl_env :: GlobalRdrEnv
ic_rn_gbl_env = InteractiveContext -> GlobalRdrEnv
ic_rn_gbl_env InteractiveContext
ictxt GlobalRdrEnv -> [TyThing] -> GlobalRdrEnv
`icExtendGblRdrEnv` [TyThing]
new_tythings }
  where
    new_tythings :: [TyThing]
new_tythings = (Id -> TyThing) -> [Id] -> [TyThing]
forall a b. (a -> b) -> [a] -> [b]
map Id -> TyThing
AnId [Id]
new_ids
    old_tythings :: [TyThing]
old_tythings = (TyThing -> Bool) -> [TyThing] -> [TyThing]
forall a. (a -> Bool) -> [a] -> [a]
filterOut ([Id] -> TyThing -> Bool
shadowed_by [Id]
new_ids) (InteractiveContext -> [TyThing]
ic_tythings InteractiveContext
ictxt)
shadowed_by :: [Id] -> TyThing -> Bool
shadowed_by :: [Id] -> TyThing -> Bool
shadowed_by ids :: [Id]
ids = TyThing -> Bool
forall a. NamedThing a => a -> Bool
shadowed
  where
    shadowed :: a -> Bool
shadowed id :: a
id = a -> OccName
forall a. NamedThing a => a -> OccName
getOccName a
id OccName -> OccSet -> Bool
`elemOccSet` OccSet
new_occs
    new_occs :: OccSet
new_occs = [OccName] -> OccSet
mkOccSet ((Id -> OccName) -> [Id] -> [OccName]
forall a b. (a -> b) -> [a] -> [b]
map Id -> OccName
forall a. NamedThing a => a -> OccName
getOccName [Id]
ids)
setInteractivePackage :: HscEnv -> HscEnv
setInteractivePackage :: HscEnv -> HscEnv
setInteractivePackage hsc_env :: HscEnv
hsc_env
   = HscEnv
hsc_env { hsc_dflags :: DynFlags
hsc_dflags = (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)
                { thisInstalledUnitId :: InstalledUnitId
thisInstalledUnitId = UnitId -> InstalledUnitId
toInstalledUnitId UnitId
interactiveUnitId } }
setInteractivePrintName :: InteractiveContext -> Name -> InteractiveContext
setInteractivePrintName :: InteractiveContext -> Name -> InteractiveContext
setInteractivePrintName ic :: InteractiveContext
ic n :: Name
n = InteractiveContext
ic{ic_int_print :: Name
ic_int_print = Name
n}
    
icExtendGblRdrEnv :: GlobalRdrEnv -> [TyThing] -> GlobalRdrEnv
icExtendGblRdrEnv :: GlobalRdrEnv -> [TyThing] -> GlobalRdrEnv
icExtendGblRdrEnv env :: GlobalRdrEnv
env tythings :: [TyThing]
tythings
  = (TyThing -> GlobalRdrEnv -> GlobalRdrEnv)
-> GlobalRdrEnv -> [TyThing] -> GlobalRdrEnv
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr TyThing -> GlobalRdrEnv -> GlobalRdrEnv
add GlobalRdrEnv
env [TyThing]
tythings  
                            
  where
    
    add :: TyThing -> GlobalRdrEnv -> GlobalRdrEnv
add thing :: TyThing
thing env :: GlobalRdrEnv
env
       | TyThing -> Bool
is_sub_bndr TyThing
thing
       = GlobalRdrEnv
env
       | Bool
otherwise
       = (GlobalRdrEnv -> GlobalRdrElt -> GlobalRdrEnv)
-> GlobalRdrEnv -> [GlobalRdrElt] -> GlobalRdrEnv
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' GlobalRdrEnv -> GlobalRdrElt -> GlobalRdrEnv
extendGlobalRdrEnv GlobalRdrEnv
env1 ((IfaceExport -> [GlobalRdrElt]) -> [IfaceExport] -> [GlobalRdrElt]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap IfaceExport -> [GlobalRdrElt]
localGREsFromAvail [IfaceExport]
avail)
       where
          env1 :: GlobalRdrEnv
env1  = GlobalRdrEnv -> [Name] -> GlobalRdrEnv
shadowNames GlobalRdrEnv
env ((IfaceExport -> [Name]) -> [IfaceExport] -> [Name]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap IfaceExport -> [Name]
availNames [IfaceExport]
avail)
          avail :: [IfaceExport]
avail = TyThing -> [IfaceExport]
tyThingAvailInfo TyThing
thing
    
    
    
    
    
    is_sub_bndr :: TyThing -> Bool
is_sub_bndr (AnId f :: Id
f) = case Id -> IdDetails
idDetails Id
f of
                             RecSelId {}  -> Bool
True
                             ClassOpId {} -> Bool
True
                             _            -> Bool
False
    is_sub_bndr _ = Bool
False
substInteractiveContext :: InteractiveContext -> TCvSubst -> InteractiveContext
substInteractiveContext :: InteractiveContext -> TCvSubst -> InteractiveContext
substInteractiveContext ictxt :: InteractiveContext
ictxt@InteractiveContext{ ic_tythings :: InteractiveContext -> [TyThing]
ic_tythings = [TyThing]
tts } subst :: TCvSubst
subst
  | TCvSubst -> Bool
isEmptyTCvSubst TCvSubst
subst = InteractiveContext
ictxt
  | Bool
otherwise             = InteractiveContext
ictxt { ic_tythings :: [TyThing]
ic_tythings = (TyThing -> TyThing) -> [TyThing] -> [TyThing]
forall a b. (a -> b) -> [a] -> [b]
map TyThing -> TyThing
subst_ty [TyThing]
tts }
  where
    subst_ty :: TyThing -> TyThing
subst_ty (AnId id :: Id
id)
      = Id -> TyThing
AnId (Id -> TyThing) -> Id -> TyThing
forall a b. (a -> b) -> a -> b
$ Id
id Id -> Type -> Id
`setIdType` TCvSubst -> Type -> Type
substTyAddInScope TCvSubst
subst (Id -> Type
idType Id
id)
      
      
      
    subst_ty tt :: TyThing
tt
      = TyThing
tt
instance Outputable InteractiveImport where
  ppr :: InteractiveImport -> SDoc
ppr (IIModule m :: ModuleName
m) = Char -> SDoc
char '*' SDoc -> SDoc -> SDoc
<> ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
m
  ppr (IIDecl d :: ImportDecl GhcPs
d)   = ImportDecl GhcPs -> SDoc
forall a. Outputable a => a -> SDoc
ppr ImportDecl GhcPs
d
mkPrintUnqualified :: DynFlags -> GlobalRdrEnv -> PrintUnqualified
mkPrintUnqualified :: DynFlags -> GlobalRdrEnv -> PrintUnqualified
mkPrintUnqualified dflags :: DynFlags
dflags env :: GlobalRdrEnv
env = QueryQualifyName
-> (Module -> Bool) -> QueryQualifyPackage -> PrintUnqualified
QueryQualify QueryQualifyName
qual_name
                                             (DynFlags -> Module -> Bool
mkQualModule DynFlags
dflags)
                                             (DynFlags -> QueryQualifyPackage
mkQualPackage DynFlags
dflags)
  where
  qual_name :: QueryQualifyName
qual_name mod :: Module
mod occ :: OccName
occ
        | [gre :: GlobalRdrElt
gre] <- [GlobalRdrElt]
unqual_gres
        , GlobalRdrElt -> Bool
right_name GlobalRdrElt
gre
        = QualifyName
NameUnqual   
                       
                       
        | [] <- [GlobalRdrElt]
unqual_gres
        , (Name -> Bool) -> [Name] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Name -> Bool
is_name [Name]
forceUnqualNames
        , Bool -> Bool
not (OccName -> Bool
isDerivedOccName OccName
occ)
        = QualifyName
NameUnqual   
                       
                       
                       
                       
                       
                       
                       
                       
                       
        | [gre :: GlobalRdrElt
gre] <- [GlobalRdrElt]
qual_gres
        = ModuleName -> QualifyName
NameQual (GlobalRdrElt -> ModuleName
greQualModName GlobalRdrElt
gre)
        | [GlobalRdrElt] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [GlobalRdrElt]
qual_gres
        = if [GlobalRdrElt] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (RdrName -> GlobalRdrEnv -> [GlobalRdrElt]
lookupGRE_RdrName (ModuleName -> OccName -> RdrName
mkRdrQual (Module -> ModuleName
moduleName Module
mod) OccName
occ) GlobalRdrEnv
env)
          then QualifyName
NameNotInScope1
          else QualifyName
NameNotInScope2
        | Bool
otherwise
        = QualifyName
NameNotInScope1   
                            
      where
        is_name :: Name -> Bool
        is_name :: Name -> Bool
is_name name :: Name
name = ASSERT2( isExternalName name, ppr name )
                       HasDebugCallStack => Name -> Module
Name -> Module
nameModule Name
name Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
== Module
mod Bool -> Bool -> Bool
&& Name -> OccName
nameOccName Name
name OccName -> OccName -> Bool
forall a. Eq a => a -> a -> Bool
== OccName
occ
        forceUnqualNames :: [Name]
        forceUnqualNames :: [Name]
forceUnqualNames =
          (TyCon -> Name) -> [TyCon] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map TyCon -> Name
tyConName [ TyCon
constraintKindTyCon, TyCon
heqTyCon, TyCon
coercibleTyCon ]
          [Name] -> [Name] -> [Name]
forall a. [a] -> [a] -> [a]
++ [ Name
eqTyConName ]
        right_name :: GlobalRdrElt -> Bool
right_name gre :: GlobalRdrElt
gre = Name -> Maybe Module
nameModule_maybe (GlobalRdrElt -> Name
gre_name GlobalRdrElt
gre) Maybe Module -> Maybe Module -> Bool
forall a. Eq a => a -> a -> Bool
== Module -> Maybe Module
forall a. a -> Maybe a
Just Module
mod
        unqual_gres :: [GlobalRdrElt]
unqual_gres = RdrName -> GlobalRdrEnv -> [GlobalRdrElt]
lookupGRE_RdrName (OccName -> RdrName
mkRdrUnqual OccName
occ) GlobalRdrEnv
env
        qual_gres :: [GlobalRdrElt]
qual_gres   = (GlobalRdrElt -> Bool) -> [GlobalRdrElt] -> [GlobalRdrElt]
forall a. (a -> Bool) -> [a] -> [a]
filter GlobalRdrElt -> Bool
right_name (GlobalRdrEnv -> OccName -> [GlobalRdrElt]
lookupGlobalRdrEnv GlobalRdrEnv
env OccName
occ)
    
    
    
mkQualModule :: DynFlags -> QueryQualifyModule
mkQualModule :: DynFlags -> Module -> Bool
mkQualModule dflags :: DynFlags
dflags mod :: Module
mod
     | Module -> UnitId
moduleUnitId Module
mod UnitId -> QueryQualifyPackage
forall a. Eq a => a -> a -> Bool
== DynFlags -> UnitId
thisPackage DynFlags
dflags = Bool
False
     | [(_, pkgconfig :: PackageConfig
pkgconfig)] <- [(Module, PackageConfig)]
lookup,
       PackageConfig -> UnitId
packageConfigId PackageConfig
pkgconfig UnitId -> QueryQualifyPackage
forall a. Eq a => a -> a -> Bool
== Module -> UnitId
moduleUnitId Module
mod
        
        
     = Bool
False
     | Bool
otherwise = Bool
True
     where lookup :: [(Module, PackageConfig)]
lookup = DynFlags -> ModuleName -> [(Module, PackageConfig)]
lookupModuleInAllPackages DynFlags
dflags (Module -> ModuleName
moduleName Module
mod)
mkQualPackage :: DynFlags -> QueryQualifyPackage
mkQualPackage :: DynFlags -> QueryQualifyPackage
mkQualPackage dflags :: DynFlags
dflags pkg_key :: UnitId
pkg_key
     | UnitId
pkg_key UnitId -> QueryQualifyPackage
forall a. Eq a => a -> a -> Bool
== UnitId
mainUnitId Bool -> Bool -> Bool
|| UnitId
pkg_key UnitId -> QueryQualifyPackage
forall a. Eq a => a -> a -> Bool
== UnitId
interactiveUnitId
        
        
     = Bool
False
     | Just pkgid :: SourcePackageId
pkgid <- Maybe SourcePackageId
mb_pkgid
     , DynFlags -> SourcePackageId -> [PackageConfig]
searchPackageId DynFlags
dflags SourcePackageId
pkgid [PackageConfig] -> Int -> Bool
forall a. [a] -> Int -> Bool
`lengthIs` 1
        
        
     = Bool
False
     | Bool
otherwise
     = Bool
True
     where mb_pkgid :: Maybe SourcePackageId
mb_pkgid = (PackageConfig -> SourcePackageId)
-> Maybe PackageConfig -> Maybe SourcePackageId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PackageConfig -> SourcePackageId
forall compid srcpkgid srcpkgname instunitid unitid modulename mod.
InstalledPackageInfo
  compid srcpkgid srcpkgname instunitid unitid modulename mod
-> srcpkgid
sourcePackageId (DynFlags -> UnitId -> Maybe PackageConfig
lookupPackage DynFlags
dflags UnitId
pkg_key)
pkgQual :: DynFlags -> PrintUnqualified
pkgQual :: DynFlags -> PrintUnqualified
pkgQual dflags :: DynFlags
dflags = PrintUnqualified
alwaysQualify {
        queryQualifyPackage :: QueryQualifyPackage
queryQualifyPackage = DynFlags -> QueryQualifyPackage
mkQualPackage DynFlags
dflags
    }
implicitTyThings :: TyThing -> [TyThing]
implicitTyThings :: TyThing -> [TyThing]
implicitTyThings (AnId _)       = []
implicitTyThings (ACoAxiom _cc :: CoAxiom Branched
_cc) = []
implicitTyThings (ATyCon tc :: TyCon
tc)    = TyCon -> [TyThing]
implicitTyConThings TyCon
tc
implicitTyThings (AConLike cl :: ConLike
cl)  = ConLike -> [TyThing]
implicitConLikeThings ConLike
cl
implicitConLikeThings :: ConLike -> [TyThing]
implicitConLikeThings :: ConLike -> [TyThing]
implicitConLikeThings (RealDataCon dc :: DataCon
dc)
  = DataCon -> [TyThing]
dataConImplicitTyThings DataCon
dc
implicitConLikeThings (PatSynCon {})
  = []  
        
        
        
        
        
        
implicitClassThings :: Class -> [TyThing]
implicitClassThings :: Class -> [TyThing]
implicitClassThings cl :: Class
cl
  = 
    
    
    
    
    (TyCon -> TyThing) -> [TyCon] -> [TyThing]
forall a b. (a -> b) -> [a] -> [b]
map TyCon -> TyThing
ATyCon (Class -> [TyCon]
classATs Class
cl) [TyThing] -> [TyThing] -> [TyThing]
forall a. [a] -> [a] -> [a]
++
    
    (Id -> TyThing) -> [Id] -> [TyThing]
forall a b. (a -> b) -> [a] -> [b]
map Id -> TyThing
AnId (Class -> [Id]
classAllSelIds Class
cl)
implicitTyConThings :: TyCon -> [TyThing]
implicitTyConThings :: TyCon -> [TyThing]
implicitTyConThings tc :: TyCon
tc
  = [TyThing]
class_stuff [TyThing] -> [TyThing] -> [TyThing]
forall a. [a] -> [a] -> [a]
++
      
      
      
    TyCon -> [TyThing]
implicitCoTyCon TyCon
tc [TyThing] -> [TyThing] -> [TyThing]
forall a. [a] -> [a] -> [a]
++
      
      
    [ TyThing
thing | DataCon
dc    <- TyCon -> [DataCon]
tyConDataCons TyCon
tc
            , TyThing
thing <- ConLike -> TyThing
AConLike (DataCon -> ConLike
RealDataCon DataCon
dc) TyThing -> [TyThing] -> [TyThing]
forall a. a -> [a] -> [a]
: DataCon -> [TyThing]
dataConImplicitTyThings DataCon
dc ]
      
      
  where
    class_stuff :: [TyThing]
class_stuff = case TyCon -> Maybe Class
tyConClass_maybe TyCon
tc of
        Nothing -> []
        Just cl :: Class
cl -> Class -> [TyThing]
implicitClassThings Class
cl
implicitCoTyCon :: TyCon -> [TyThing]
implicitCoTyCon :: TyCon -> [TyThing]
implicitCoTyCon tc :: TyCon
tc
  | Just co :: CoAxiom Unbranched
co <- TyCon -> Maybe (CoAxiom Unbranched)
newTyConCo_maybe TyCon
tc = [CoAxiom Branched -> TyThing
ACoAxiom (CoAxiom Branched -> TyThing) -> CoAxiom Branched -> TyThing
forall a b. (a -> b) -> a -> b
$ CoAxiom Unbranched -> CoAxiom Branched
forall (br :: BranchFlag). CoAxiom br -> CoAxiom Branched
toBranchedAxiom CoAxiom Unbranched
co]
  | Just co :: CoAxiom Branched
co <- TyCon -> Maybe (CoAxiom Branched)
isClosedSynFamilyTyConWithAxiom_maybe TyCon
tc
                                   = [CoAxiom Branched -> TyThing
ACoAxiom CoAxiom Branched
co]
  | Bool
otherwise                      = []
isImplicitTyThing :: TyThing -> Bool
isImplicitTyThing :: TyThing -> Bool
isImplicitTyThing (AConLike cl :: ConLike
cl) = case ConLike
cl of
                                    RealDataCon {} -> Bool
True
                                    PatSynCon {}   -> Bool
False
isImplicitTyThing (AnId id :: Id
id)     = Id -> Bool
isImplicitId Id
id
isImplicitTyThing (ATyCon tc :: TyCon
tc)   = TyCon -> Bool
isImplicitTyCon TyCon
tc
isImplicitTyThing (ACoAxiom ax :: CoAxiom Branched
ax) = CoAxiom Branched -> Bool
forall (br :: BranchFlag). CoAxiom br -> Bool
isImplicitCoAxiom CoAxiom Branched
ax
tyThingParent_maybe :: TyThing -> Maybe TyThing
tyThingParent_maybe :: TyThing -> Maybe TyThing
tyThingParent_maybe (AConLike cl :: ConLike
cl) = case ConLike
cl of
    RealDataCon dc :: DataCon
dc  -> TyThing -> Maybe TyThing
forall a. a -> Maybe a
Just (TyCon -> TyThing
ATyCon (DataCon -> TyCon
dataConTyCon DataCon
dc))
    PatSynCon{}     -> Maybe TyThing
forall a. Maybe a
Nothing
tyThingParent_maybe (ATyCon tc :: TyCon
tc)   = case TyCon -> Maybe TyCon
tyConAssoc_maybe TyCon
tc of
                                      Just tc :: TyCon
tc -> TyThing -> Maybe TyThing
forall a. a -> Maybe a
Just (TyCon -> TyThing
ATyCon TyCon
tc)
                                      Nothing -> Maybe TyThing
forall a. Maybe a
Nothing
tyThingParent_maybe (AnId id :: Id
id)     = case Id -> IdDetails
idDetails Id
id of
                                      RecSelId { sel_tycon :: IdDetails -> RecSelParent
sel_tycon = RecSelData tc :: TyCon
tc } ->
                                          TyThing -> Maybe TyThing
forall a. a -> Maybe a
Just (TyCon -> TyThing
ATyCon TyCon
tc)
                                      ClassOpId cls :: Class
cls               ->
                                          TyThing -> Maybe TyThing
forall a. a -> Maybe a
Just (TyCon -> TyThing
ATyCon (Class -> TyCon
classTyCon Class
cls))
                                      _other :: IdDetails
_other                      -> Maybe TyThing
forall a. Maybe a
Nothing
tyThingParent_maybe _other :: TyThing
_other = Maybe TyThing
forall a. Maybe a
Nothing
tyThingsTyCoVars :: [TyThing] -> TyCoVarSet
tyThingsTyCoVars :: [TyThing] -> TyCoVarSet
tyThingsTyCoVars tts :: [TyThing]
tts =
    [TyCoVarSet] -> TyCoVarSet
unionVarSets ([TyCoVarSet] -> TyCoVarSet) -> [TyCoVarSet] -> TyCoVarSet
forall a b. (a -> b) -> a -> b
$ (TyThing -> TyCoVarSet) -> [TyThing] -> [TyCoVarSet]
forall a b. (a -> b) -> [a] -> [b]
map TyThing -> TyCoVarSet
ttToVarSet [TyThing]
tts
    where
        ttToVarSet :: TyThing -> TyCoVarSet
ttToVarSet (AnId id :: Id
id)     = Type -> TyCoVarSet
tyCoVarsOfType (Type -> TyCoVarSet) -> Type -> TyCoVarSet
forall a b. (a -> b) -> a -> b
$ Id -> Type
idType Id
id
        ttToVarSet (AConLike cl :: ConLike
cl) = case ConLike
cl of
            RealDataCon dc :: DataCon
dc  -> Type -> TyCoVarSet
tyCoVarsOfType (Type -> TyCoVarSet) -> Type -> TyCoVarSet
forall a b. (a -> b) -> a -> b
$ DataCon -> Type
dataConRepType DataCon
dc
            PatSynCon{}     -> TyCoVarSet
emptyVarSet
        ttToVarSet (ATyCon tc :: TyCon
tc)
          = case TyCon -> Maybe Class
tyConClass_maybe TyCon
tc of
              Just cls :: Class
cls -> ([Id] -> TyCoVarSet
mkVarSet ([Id] -> TyCoVarSet) -> (Class -> [Id]) -> Class -> TyCoVarSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Id], [FunDep Id]) -> [Id]
forall a b. (a, b) -> a
fst (([Id], [FunDep Id]) -> [Id])
-> (Class -> ([Id], [FunDep Id])) -> Class -> [Id]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Class -> ([Id], [FunDep Id])
classTvsFds) Class
cls
              Nothing  -> Type -> TyCoVarSet
tyCoVarsOfType (Type -> TyCoVarSet) -> Type -> TyCoVarSet
forall a b. (a -> b) -> a -> b
$ TyCon -> Type
tyConKind TyCon
tc
        ttToVarSet (ACoAxiom _)  = TyCoVarSet
emptyVarSet
tyThingAvailInfo :: TyThing -> [AvailInfo]
tyThingAvailInfo :: TyThing -> [IfaceExport]
tyThingAvailInfo (ATyCon t :: TyCon
t)
   = case TyCon -> Maybe Class
tyConClass_maybe TyCon
t of
        Just c :: Class
c  -> [Name -> [Name] -> [FieldLabel] -> IfaceExport
AvailTC Name
n (Name
n Name -> [Name] -> [Name]
forall a. a -> [a] -> [a]
: (Id -> Name) -> [Id] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map Id -> Name
forall a. NamedThing a => a -> Name
getName (Class -> [Id]
classMethods Class
c)
                                 [Name] -> [Name] -> [Name]
forall a. [a] -> [a] -> [a]
++ (TyCon -> Name) -> [TyCon] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map TyCon -> Name
forall a. NamedThing a => a -> Name
getName (Class -> [TyCon]
classATs Class
c))
                             [] ]
             where n :: Name
n = Class -> Name
forall a. NamedThing a => a -> Name
getName Class
c
        Nothing -> [Name -> [Name] -> [FieldLabel] -> IfaceExport
AvailTC Name
n (Name
n Name -> [Name] -> [Name]
forall a. a -> [a] -> [a]
: (DataCon -> Name) -> [DataCon] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map DataCon -> Name
forall a. NamedThing a => a -> Name
getName [DataCon]
dcs) [FieldLabel]
flds]
             where n :: Name
n    = TyCon -> Name
forall a. NamedThing a => a -> Name
getName TyCon
t
                   dcs :: [DataCon]
dcs  = TyCon -> [DataCon]
tyConDataCons TyCon
t
                   flds :: [FieldLabel]
flds = TyCon -> [FieldLabel]
tyConFieldLabels TyCon
t
tyThingAvailInfo (AConLike (PatSynCon p :: PatSyn
p))
  = (Name -> IfaceExport) -> [Name] -> [IfaceExport]
forall a b. (a -> b) -> [a] -> [b]
map Name -> IfaceExport
avail ((PatSyn -> Name
forall a. NamedThing a => a -> Name
getName PatSyn
p) Name -> [Name] -> [Name]
forall a. a -> [a] -> [a]
: (FieldLabel -> Name) -> [FieldLabel] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map FieldLabel -> Name
forall a. FieldLbl a -> a
flSelector (PatSyn -> [FieldLabel]
patSynFieldLabels PatSyn
p))
tyThingAvailInfo t :: TyThing
t
   = [Name -> IfaceExport
avail (TyThing -> Name
forall a. NamedThing a => a -> Name
getName TyThing
t)]
type TypeEnv = NameEnv TyThing
emptyTypeEnv    :: TypeEnv
typeEnvElts     :: TypeEnv -> [TyThing]
typeEnvTyCons   :: TypeEnv -> [TyCon]
typeEnvCoAxioms :: TypeEnv -> [CoAxiom Branched]
typeEnvIds      :: TypeEnv -> [Id]
typeEnvPatSyns  :: TypeEnv -> [PatSyn]
typeEnvDataCons :: TypeEnv -> [DataCon]
typeEnvClasses  :: TypeEnv -> [Class]
lookupTypeEnv   :: TypeEnv -> Name -> Maybe TyThing
emptyTypeEnv :: TypeEnv
emptyTypeEnv        = TypeEnv
forall a. NameEnv a
emptyNameEnv
typeEnvElts :: TypeEnv -> [TyThing]
typeEnvElts     env :: TypeEnv
env = TypeEnv -> [TyThing]
forall a. NameEnv a -> [a]
nameEnvElts TypeEnv
env
typeEnvTyCons :: TypeEnv -> [TyCon]
typeEnvTyCons   env :: TypeEnv
env = [TyCon
tc | ATyCon tc :: TyCon
tc   <- TypeEnv -> [TyThing]
typeEnvElts TypeEnv
env]
typeEnvCoAxioms :: TypeEnv -> [CoAxiom Branched]
typeEnvCoAxioms env :: TypeEnv
env = [CoAxiom Branched
ax | ACoAxiom ax :: CoAxiom Branched
ax <- TypeEnv -> [TyThing]
typeEnvElts TypeEnv
env]
typeEnvIds :: TypeEnv -> [Id]
typeEnvIds      env :: TypeEnv
env = [Id
id | AnId id :: Id
id     <- TypeEnv -> [TyThing]
typeEnvElts TypeEnv
env]
typeEnvPatSyns :: TypeEnv -> [PatSyn]
typeEnvPatSyns  env :: TypeEnv
env = [PatSyn
ps | AConLike (PatSynCon ps :: PatSyn
ps) <- TypeEnv -> [TyThing]
typeEnvElts TypeEnv
env]
typeEnvDataCons :: TypeEnv -> [DataCon]
typeEnvDataCons env :: TypeEnv
env = [DataCon
dc | AConLike (RealDataCon dc :: DataCon
dc) <- TypeEnv -> [TyThing]
typeEnvElts TypeEnv
env]
typeEnvClasses :: TypeEnv -> [Class]
typeEnvClasses  env :: TypeEnv
env = [Class
cl | TyCon
tc <- TypeEnv -> [TyCon]
typeEnvTyCons TypeEnv
env,
                            Just cl :: Class
cl <- [TyCon -> Maybe Class
tyConClass_maybe TyCon
tc]]
mkTypeEnv :: [TyThing] -> TypeEnv
mkTypeEnv :: [TyThing] -> TypeEnv
mkTypeEnv things :: [TyThing]
things = TypeEnv -> [TyThing] -> TypeEnv
extendTypeEnvList TypeEnv
emptyTypeEnv [TyThing]
things
mkTypeEnvWithImplicits :: [TyThing] -> TypeEnv
mkTypeEnvWithImplicits :: [TyThing] -> TypeEnv
mkTypeEnvWithImplicits things :: [TyThing]
things =
  [TyThing] -> TypeEnv
mkTypeEnv [TyThing]
things
    TypeEnv -> TypeEnv -> TypeEnv
forall a. NameEnv a -> NameEnv a -> NameEnv a
`plusNameEnv`
  [TyThing] -> TypeEnv
mkTypeEnv ((TyThing -> [TyThing]) -> [TyThing] -> [TyThing]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TyThing -> [TyThing]
implicitTyThings [TyThing]
things)
typeEnvFromEntities :: [Id] -> [TyCon] -> [FamInst] -> TypeEnv
typeEnvFromEntities :: [Id] -> [TyCon] -> [FamInst] -> TypeEnv
typeEnvFromEntities ids :: [Id]
ids tcs :: [TyCon]
tcs famInsts :: [FamInst]
famInsts =
  [TyThing] -> TypeEnv
mkTypeEnv (   (Id -> TyThing) -> [Id] -> [TyThing]
forall a b. (a -> b) -> [a] -> [b]
map Id -> TyThing
AnId [Id]
ids
             [TyThing] -> [TyThing] -> [TyThing]
forall a. [a] -> [a] -> [a]
++ (TyCon -> TyThing) -> [TyCon] -> [TyThing]
forall a b. (a -> b) -> [a] -> [b]
map TyCon -> TyThing
ATyCon [TyCon]
all_tcs
             [TyThing] -> [TyThing] -> [TyThing]
forall a. [a] -> [a] -> [a]
++ (TyCon -> [TyThing]) -> [TyCon] -> [TyThing]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TyCon -> [TyThing]
implicitTyConThings [TyCon]
all_tcs
             [TyThing] -> [TyThing] -> [TyThing]
forall a. [a] -> [a] -> [a]
++ (FamInst -> TyThing) -> [FamInst] -> [TyThing]
forall a b. (a -> b) -> [a] -> [b]
map (CoAxiom Branched -> TyThing
ACoAxiom (CoAxiom Branched -> TyThing)
-> (FamInst -> CoAxiom Branched) -> FamInst -> TyThing
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CoAxiom Unbranched -> CoAxiom Branched
forall (br :: BranchFlag). CoAxiom br -> CoAxiom Branched
toBranchedAxiom (CoAxiom Unbranched -> CoAxiom Branched)
-> (FamInst -> CoAxiom Unbranched) -> FamInst -> CoAxiom Branched
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FamInst -> CoAxiom Unbranched
famInstAxiom) [FamInst]
famInsts
            )
 where
  all_tcs :: [TyCon]
all_tcs = [TyCon]
tcs [TyCon] -> [TyCon] -> [TyCon]
forall a. [a] -> [a] -> [a]
++ [FamInst] -> [TyCon]
famInstsRepTyCons [FamInst]
famInsts
lookupTypeEnv :: TypeEnv -> Name -> Maybe TyThing
lookupTypeEnv = TypeEnv -> Name -> Maybe TyThing
forall a. NameEnv a -> Name -> Maybe a
lookupNameEnv
extendTypeEnv :: TypeEnv -> TyThing -> TypeEnv
extendTypeEnv :: TypeEnv -> TyThing -> TypeEnv
extendTypeEnv env :: TypeEnv
env thing :: TyThing
thing = TypeEnv -> Name -> TyThing -> TypeEnv
forall a. NameEnv a -> Name -> a -> NameEnv a
extendNameEnv TypeEnv
env (TyThing -> Name
forall a. NamedThing a => a -> Name
getName TyThing
thing) TyThing
thing
extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv
extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv
extendTypeEnvList env :: TypeEnv
env things :: [TyThing]
things = (TypeEnv -> TyThing -> TypeEnv) -> TypeEnv -> [TyThing] -> TypeEnv
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' TypeEnv -> TyThing -> TypeEnv
extendTypeEnv TypeEnv
env [TyThing]
things
extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv
extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv
extendTypeEnvWithIds env :: TypeEnv
env ids :: [Id]
ids
  = TypeEnv -> [(Name, TyThing)] -> TypeEnv
forall a. NameEnv a -> [(Name, a)] -> NameEnv a
extendNameEnvList TypeEnv
env [(Id -> Name
forall a. NamedThing a => a -> Name
getName Id
id, Id -> TyThing
AnId Id
id) | Id
id <- [Id]
ids]
plusTypeEnv :: TypeEnv -> TypeEnv -> TypeEnv
plusTypeEnv :: TypeEnv -> TypeEnv -> TypeEnv
plusTypeEnv env1 :: TypeEnv
env1 env2 :: TypeEnv
env2 = TypeEnv -> TypeEnv -> TypeEnv
forall a. NameEnv a -> NameEnv a -> NameEnv a
plusNameEnv TypeEnv
env1 TypeEnv
env2
lookupType :: DynFlags
           -> HomePackageTable
           -> PackageTypeEnv
           -> Name
           -> Maybe TyThing
lookupType :: DynFlags -> HomePackageTable -> TypeEnv -> Name -> Maybe TyThing
lookupType dflags :: DynFlags
dflags hpt :: HomePackageTable
hpt pte :: TypeEnv
pte name :: Name
name
  | GhcMode -> Bool
isOneShot (DynFlags -> GhcMode
ghcMode DynFlags
dflags)  
  = TypeEnv -> Name -> Maybe TyThing
forall a. NameEnv a -> Name -> Maybe a
lookupNameEnv TypeEnv
pte Name
name
  | Bool
otherwise
  = case HomePackageTable -> Module -> Maybe HomeModInfo
lookupHptByModule HomePackageTable
hpt Module
mod of
       Just hm :: HomeModInfo
hm -> TypeEnv -> Name -> Maybe TyThing
forall a. NameEnv a -> Name -> Maybe a
lookupNameEnv (ModDetails -> TypeEnv
md_types (HomeModInfo -> ModDetails
hm_details HomeModInfo
hm)) Name
name
       Nothing -> TypeEnv -> Name -> Maybe TyThing
forall a. NameEnv a -> Name -> Maybe a
lookupNameEnv TypeEnv
pte Name
name
  where
    mod :: Module
mod = ASSERT2( isExternalName name, ppr name )
          if Name -> Bool
isHoleName Name
name
            then UnitId -> ModuleName -> Module
mkModule (DynFlags -> UnitId
thisPackage DynFlags
dflags) (Module -> ModuleName
moduleName (HasDebugCallStack => Name -> Module
Name -> Module
nameModule Name
name))
            else HasDebugCallStack => Name -> Module
Name -> Module
nameModule Name
name
lookupTypeHscEnv :: HscEnv -> Name -> IO (Maybe TyThing)
lookupTypeHscEnv :: HscEnv -> Name -> IO (Maybe TyThing)
lookupTypeHscEnv hsc_env :: HscEnv
hsc_env name :: Name
name = do
    ExternalPackageState
eps <- IORef ExternalPackageState -> IO ExternalPackageState
forall a. IORef a -> IO a
readIORef (HscEnv -> IORef ExternalPackageState
hsc_EPS HscEnv
hsc_env)
    Maybe TyThing -> IO (Maybe TyThing)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe TyThing -> IO (Maybe TyThing))
-> Maybe TyThing -> IO (Maybe TyThing)
forall a b. (a -> b) -> a -> b
$! DynFlags -> HomePackageTable -> TypeEnv -> Name -> Maybe TyThing
lookupType DynFlags
dflags HomePackageTable
hpt (ExternalPackageState -> TypeEnv
eps_PTE ExternalPackageState
eps) Name
name
  where
    dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
    hpt :: HomePackageTable
hpt = HscEnv -> HomePackageTable
hsc_HPT HscEnv
hsc_env
tyThingTyCon :: TyThing -> TyCon
tyThingTyCon :: TyThing -> TyCon
tyThingTyCon (ATyCon tc :: TyCon
tc) = TyCon
tc
tyThingTyCon other :: TyThing
other       = String -> SDoc -> TyCon
forall a. HasCallStack => String -> SDoc -> a
pprPanic "tyThingTyCon" (TyThing -> SDoc
forall a. Outputable a => a -> SDoc
ppr TyThing
other)
tyThingCoAxiom :: TyThing -> CoAxiom Branched
tyThingCoAxiom :: TyThing -> CoAxiom Branched
tyThingCoAxiom (ACoAxiom ax :: CoAxiom Branched
ax) = CoAxiom Branched
ax
tyThingCoAxiom other :: TyThing
other         = String -> SDoc -> CoAxiom Branched
forall a. HasCallStack => String -> SDoc -> a
pprPanic "tyThingCoAxiom" (TyThing -> SDoc
forall a. Outputable a => a -> SDoc
ppr TyThing
other)
tyThingDataCon :: TyThing -> DataCon
tyThingDataCon :: TyThing -> DataCon
tyThingDataCon (AConLike (RealDataCon dc :: DataCon
dc)) = DataCon
dc
tyThingDataCon other :: TyThing
other                       = String -> SDoc -> DataCon
forall a. HasCallStack => String -> SDoc -> a
pprPanic "tyThingDataCon" (TyThing -> SDoc
forall a. Outputable a => a -> SDoc
ppr TyThing
other)
tyThingConLike :: TyThing -> ConLike
tyThingConLike :: TyThing -> ConLike
tyThingConLike (AConLike dc :: ConLike
dc) = ConLike
dc
tyThingConLike other :: TyThing
other         = String -> SDoc -> ConLike
forall a. HasCallStack => String -> SDoc -> a
pprPanic "tyThingConLike" (TyThing -> SDoc
forall a. Outputable a => a -> SDoc
ppr TyThing
other)
tyThingId :: TyThing -> Id
tyThingId :: TyThing -> Id
tyThingId (AnId id :: Id
id)                   = Id
id
tyThingId (AConLike (RealDataCon dc :: DataCon
dc)) = DataCon -> Id
dataConWrapId DataCon
dc
tyThingId other :: TyThing
other                       = String -> SDoc -> Id
forall a. HasCallStack => String -> SDoc -> a
pprPanic "tyThingId" (TyThing -> SDoc
forall a. Outputable a => a -> SDoc
ppr TyThing
other)
class Monad m => MonadThings m where
        lookupThing :: Name -> m TyThing
        lookupId :: Name -> m Id
        lookupId = (TyThing -> Id) -> m TyThing -> m Id
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM TyThing -> Id
tyThingId (m TyThing -> m Id) -> (Name -> m TyThing) -> Name -> m Id
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> m TyThing
forall (m :: * -> *). MonadThings m => Name -> m TyThing
lookupThing
        lookupDataCon :: Name -> m DataCon
        lookupDataCon = (TyThing -> DataCon) -> m TyThing -> m DataCon
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM TyThing -> DataCon
tyThingDataCon (m TyThing -> m DataCon)
-> (Name -> m TyThing) -> Name -> m DataCon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> m TyThing
forall (m :: * -> *). MonadThings m => Name -> m TyThing
lookupThing
        lookupTyCon :: Name -> m TyCon
        lookupTyCon = (TyThing -> TyCon) -> m TyThing -> m TyCon
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM TyThing -> TyCon
tyThingTyCon (m TyThing -> m TyCon) -> (Name -> m TyThing) -> Name -> m TyCon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> m TyThing
forall (m :: * -> *). MonadThings m => Name -> m TyThing
lookupThing
data Warnings
  = NoWarnings                          
  | WarnAll WarningTxt                  
  | WarnSome [(OccName,WarningTxt)]     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
  deriving( Warnings -> Warnings -> Bool
(Warnings -> Warnings -> Bool)
-> (Warnings -> Warnings -> Bool) -> Eq Warnings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Warnings -> Warnings -> Bool
$c/= :: Warnings -> Warnings -> Bool
== :: Warnings -> Warnings -> Bool
$c== :: Warnings -> Warnings -> Bool
Eq )
instance Binary Warnings where
    put_ :: BinHandle -> Warnings -> IO ()
put_ bh :: BinHandle
bh NoWarnings     = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh 0
    put_ bh :: BinHandle
bh (WarnAll t :: WarningTxt
t) = do
            BinHandle -> Word8 -> IO ()
putByte BinHandle
bh 1
            BinHandle -> WarningTxt -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh WarningTxt
t
    put_ bh :: BinHandle
bh (WarnSome ts :: [(OccName, WarningTxt)]
ts) = do
            BinHandle -> Word8 -> IO ()
putByte BinHandle
bh 2
            BinHandle -> [(OccName, WarningTxt)] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [(OccName, WarningTxt)]
ts
    get :: BinHandle -> IO Warnings
get bh :: BinHandle
bh = do
            Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
            case Word8
h of
              0 -> Warnings -> IO Warnings
forall (m :: * -> *) a. Monad m => a -> m a
return Warnings
NoWarnings
              1 -> do WarningTxt
aa <- BinHandle -> IO WarningTxt
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                      Warnings -> IO Warnings
forall (m :: * -> *) a. Monad m => a -> m a
return (WarningTxt -> Warnings
WarnAll WarningTxt
aa)
              _ -> do [(OccName, WarningTxt)]
aa <- BinHandle -> IO [(OccName, WarningTxt)]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                      Warnings -> IO Warnings
forall (m :: * -> *) a. Monad m => a -> m a
return ([(OccName, WarningTxt)] -> Warnings
WarnSome [(OccName, WarningTxt)]
aa)
mkIfaceWarnCache :: Warnings -> OccName -> Maybe WarningTxt
mkIfaceWarnCache :: Warnings -> OccName -> Maybe WarningTxt
mkIfaceWarnCache NoWarnings  = \_ -> Maybe WarningTxt
forall a. Maybe a
Nothing
mkIfaceWarnCache (WarnAll t :: WarningTxt
t) = \_ -> WarningTxt -> Maybe WarningTxt
forall a. a -> Maybe a
Just WarningTxt
t
mkIfaceWarnCache (WarnSome pairs :: [(OccName, WarningTxt)]
pairs) = OccEnv WarningTxt -> OccName -> Maybe WarningTxt
forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv ([(OccName, WarningTxt)] -> OccEnv WarningTxt
forall a. [(OccName, a)] -> OccEnv a
mkOccEnv [(OccName, WarningTxt)]
pairs)
emptyIfaceWarnCache :: OccName -> Maybe WarningTxt
emptyIfaceWarnCache :: OccName -> Maybe WarningTxt
emptyIfaceWarnCache _ = Maybe WarningTxt
forall a. Maybe a
Nothing
plusWarns :: Warnings -> Warnings -> Warnings
plusWarns :: Warnings -> Warnings -> Warnings
plusWarns d :: Warnings
d NoWarnings = Warnings
d
plusWarns NoWarnings d :: Warnings
d = Warnings
d
plusWarns _ (WarnAll t :: WarningTxt
t) = WarningTxt -> Warnings
WarnAll WarningTxt
t
plusWarns (WarnAll t :: WarningTxt
t) _ = WarningTxt -> Warnings
WarnAll WarningTxt
t
plusWarns (WarnSome v1 :: [(OccName, WarningTxt)]
v1) (WarnSome v2 :: [(OccName, WarningTxt)]
v2) = [(OccName, WarningTxt)] -> Warnings
WarnSome ([(OccName, WarningTxt)]
v1 [(OccName, WarningTxt)]
-> [(OccName, WarningTxt)] -> [(OccName, WarningTxt)]
forall a. [a] -> [a] -> [a]
++ [(OccName, WarningTxt)]
v2)
mkIfaceFixCache :: [(OccName, Fixity)] -> OccName -> Maybe Fixity
mkIfaceFixCache :: [(OccName, Fixity)] -> OccName -> Maybe Fixity
mkIfaceFixCache pairs :: [(OccName, Fixity)]
pairs
  = \n :: OccName
n -> OccEnv Fixity -> OccName -> Maybe Fixity
forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv OccEnv Fixity
env OccName
n
  where
   env :: OccEnv Fixity
env = [(OccName, Fixity)] -> OccEnv Fixity
forall a. [(OccName, a)] -> OccEnv a
mkOccEnv [(OccName, Fixity)]
pairs
emptyIfaceFixCache :: OccName -> Maybe Fixity
emptyIfaceFixCache :: OccName -> Maybe Fixity
emptyIfaceFixCache _ = Maybe Fixity
forall a. Maybe a
Nothing
type FixityEnv = NameEnv FixItem
data FixItem = FixItem OccName Fixity
instance Outputable FixItem where
  ppr :: FixItem -> SDoc
ppr (FixItem occ :: OccName
occ fix :: Fixity
fix) = Fixity -> SDoc
forall a. Outputable a => a -> SDoc
ppr Fixity
fix SDoc -> SDoc -> SDoc
<+> OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr OccName
occ
emptyFixityEnv :: FixityEnv
emptyFixityEnv :: FixityEnv
emptyFixityEnv = FixityEnv
forall a. NameEnv a
emptyNameEnv
lookupFixity :: FixityEnv -> Name -> Fixity
lookupFixity :: FixityEnv -> Name -> Fixity
lookupFixity env :: FixityEnv
env n :: Name
n = case FixityEnv -> Name -> Maybe FixItem
forall a. NameEnv a -> Name -> Maybe a
lookupNameEnv FixityEnv
env Name
n of
                        Just (FixItem _ fix :: Fixity
fix) -> Fixity
fix
                        Nothing         -> Fixity
defaultFixity
type WhetherHasOrphans   = Bool
type WhetherHasFamInst = Bool
type IsBootInterface = Bool
data Dependencies
  = Deps { Dependencies -> [(ModuleName, Bool)]
dep_mods   :: [(ModuleName, IsBootInterface)]
                        
                        
                        
         , Dependencies -> [(InstalledUnitId, Bool)]
dep_pkgs   :: [(InstalledUnitId, Bool)]
                        
                        
                        
                        
                        
                        
         , Dependencies -> [Module]
dep_orphs  :: [Module]
                        
                        
                        
                        
                        
                        
                        
                        
         , Dependencies -> [Module]
dep_finsts :: [Module]
                        
                        
                        
                        
                        
         , Dependencies -> [ModuleName]
dep_plgins :: [ModuleName]
                        
         }
  deriving( Dependencies -> Dependencies -> Bool
(Dependencies -> Dependencies -> Bool)
-> (Dependencies -> Dependencies -> Bool) -> Eq Dependencies
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Dependencies -> Dependencies -> Bool
$c/= :: Dependencies -> Dependencies -> Bool
== :: Dependencies -> Dependencies -> Bool
$c== :: Dependencies -> Dependencies -> Bool
Eq )
        
        
instance Binary Dependencies where
    put_ :: BinHandle -> Dependencies -> IO ()
put_ bh :: BinHandle
bh deps :: Dependencies
deps = do BinHandle -> [(ModuleName, Bool)] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Dependencies -> [(ModuleName, Bool)]
dep_mods Dependencies
deps)
                      BinHandle -> [(InstalledUnitId, Bool)] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Dependencies -> [(InstalledUnitId, Bool)]
dep_pkgs Dependencies
deps)
                      BinHandle -> [Module] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Dependencies -> [Module]
dep_orphs Dependencies
deps)
                      BinHandle -> [Module] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Dependencies -> [Module]
dep_finsts Dependencies
deps)
                      BinHandle -> [ModuleName] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Dependencies -> [ModuleName]
dep_plgins Dependencies
deps)
    get :: BinHandle -> IO Dependencies
get bh :: BinHandle
bh = do [(ModuleName, Bool)]
ms <- BinHandle -> IO [(ModuleName, Bool)]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                [(InstalledUnitId, Bool)]
ps <- BinHandle -> IO [(InstalledUnitId, Bool)]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                [Module]
os <- BinHandle -> IO [Module]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                [Module]
fis <- BinHandle -> IO [Module]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                [ModuleName]
pl <- BinHandle -> IO [ModuleName]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                Dependencies -> IO Dependencies
forall (m :: * -> *) a. Monad m => a -> m a
return (Deps :: [(ModuleName, Bool)]
-> [(InstalledUnitId, Bool)]
-> [Module]
-> [Module]
-> [ModuleName]
-> Dependencies
Deps { dep_mods :: [(ModuleName, Bool)]
dep_mods = [(ModuleName, Bool)]
ms, dep_pkgs :: [(InstalledUnitId, Bool)]
dep_pkgs = [(InstalledUnitId, Bool)]
ps, dep_orphs :: [Module]
dep_orphs = [Module]
os,
                               dep_finsts :: [Module]
dep_finsts = [Module]
fis, dep_plgins :: [ModuleName]
dep_plgins = [ModuleName]
pl })
noDependencies :: Dependencies
noDependencies :: Dependencies
noDependencies = [(ModuleName, Bool)]
-> [(InstalledUnitId, Bool)]
-> [Module]
-> [Module]
-> [ModuleName]
-> Dependencies
Deps [] [] [] [] []
data Usage
  
  = UsagePackageModule {
        Usage -> Module
usg_mod      :: Module,
           
        Usage -> Fingerprint
usg_mod_hash :: Fingerprint,
            
        Usage -> Bool
usg_safe :: IsSafeImport
            
    }
  
  | UsageHomeModule {
        Usage -> ModuleName
usg_mod_name :: ModuleName,
            
        usg_mod_hash :: Fingerprint,
            
        Usage -> [(OccName, Fingerprint)]
usg_entities :: [(OccName,Fingerprint)],
            
            
            
        Usage -> Maybe Fingerprint
usg_exports  :: Maybe Fingerprint,
            
            
        usg_safe :: IsSafeImport
            
    }                                           
  
  
  | UsageFile {
        Usage -> String
usg_file_path  :: FilePath,
        
        
        Usage -> Fingerprint
usg_file_hash  :: Fingerprint
        
        
        
        
        
  }
  
  | UsageMergedRequirement {
        usg_mod :: Module,
        usg_mod_hash :: Fingerprint
  }
    deriving( Usage -> Usage -> Bool
(Usage -> Usage -> Bool) -> (Usage -> Usage -> Bool) -> Eq Usage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Usage -> Usage -> Bool
$c/= :: Usage -> Usage -> Bool
== :: Usage -> Usage -> Bool
$c== :: Usage -> Usage -> Bool
Eq )
        
        
        
        
        
        
        
        
        
        
        
        
instance Binary Usage where
    put_ :: BinHandle -> Usage -> IO ()
put_ bh :: BinHandle
bh usg :: Usage
usg@UsagePackageModule{} = do
        BinHandle -> Word8 -> IO ()
putByte BinHandle
bh 0
        BinHandle -> Module -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> Module
usg_mod Usage
usg)
        BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> Fingerprint
usg_mod_hash Usage
usg)
        BinHandle -> Bool -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> Bool
usg_safe     Usage
usg)
    put_ bh :: BinHandle
bh usg :: Usage
usg@UsageHomeModule{} = do
        BinHandle -> Word8 -> IO ()
putByte BinHandle
bh 1
        BinHandle -> ModuleName -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> ModuleName
usg_mod_name Usage
usg)
        BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> Fingerprint
usg_mod_hash Usage
usg)
        BinHandle -> Maybe Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> Maybe Fingerprint
usg_exports  Usage
usg)
        BinHandle -> [(OccName, Fingerprint)] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> [(OccName, Fingerprint)]
usg_entities Usage
usg)
        BinHandle -> Bool -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> Bool
usg_safe     Usage
usg)
    put_ bh :: BinHandle
bh usg :: Usage
usg@UsageFile{} = do
        BinHandle -> Word8 -> IO ()
putByte BinHandle
bh 2
        BinHandle -> String -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> String
usg_file_path Usage
usg)
        BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> Fingerprint
usg_file_hash Usage
usg)
    put_ bh :: BinHandle
bh usg :: Usage
usg@UsageMergedRequirement{} = do
        BinHandle -> Word8 -> IO ()
putByte BinHandle
bh 3
        BinHandle -> Module -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> Module
usg_mod      Usage
usg)
        BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Usage -> Fingerprint
usg_mod_hash Usage
usg)
    get :: BinHandle -> IO Usage
get bh :: BinHandle
bh = do
        Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
        case Word8
h of
          0 -> do
            Module
nm    <- BinHandle -> IO Module
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Fingerprint
mod   <- BinHandle -> IO Fingerprint
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Bool
safe  <- BinHandle -> IO Bool
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Usage -> IO Usage
forall (m :: * -> *) a. Monad m => a -> m a
return UsagePackageModule :: Module -> Fingerprint -> Bool -> Usage
UsagePackageModule { usg_mod :: Module
usg_mod = Module
nm, usg_mod_hash :: Fingerprint
usg_mod_hash = Fingerprint
mod, usg_safe :: Bool
usg_safe = Bool
safe }
          1 -> do
            ModuleName
nm    <- BinHandle -> IO ModuleName
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Fingerprint
mod   <- BinHandle -> IO Fingerprint
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Maybe Fingerprint
exps  <- BinHandle -> IO (Maybe Fingerprint)
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            [(OccName, Fingerprint)]
ents  <- BinHandle -> IO [(OccName, Fingerprint)]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Bool
safe  <- BinHandle -> IO Bool
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Usage -> IO Usage
forall (m :: * -> *) a. Monad m => a -> m a
return UsageHomeModule :: ModuleName
-> Fingerprint
-> [(OccName, Fingerprint)]
-> Maybe Fingerprint
-> Bool
-> Usage
UsageHomeModule { usg_mod_name :: ModuleName
usg_mod_name = ModuleName
nm, usg_mod_hash :: Fingerprint
usg_mod_hash = Fingerprint
mod,
                     usg_exports :: Maybe Fingerprint
usg_exports = Maybe Fingerprint
exps, usg_entities :: [(OccName, Fingerprint)]
usg_entities = [(OccName, Fingerprint)]
ents, usg_safe :: Bool
usg_safe = Bool
safe }
          2 -> do
            String
fp   <- BinHandle -> IO String
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Fingerprint
hash <- BinHandle -> IO Fingerprint
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Usage -> IO Usage
forall (m :: * -> *) a. Monad m => a -> m a
return UsageFile :: String -> Fingerprint -> Usage
UsageFile { usg_file_path :: String
usg_file_path = String
fp, usg_file_hash :: Fingerprint
usg_file_hash = Fingerprint
hash }
          3 -> do
            Module
mod <- BinHandle -> IO Module
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Fingerprint
hash <- BinHandle -> IO Fingerprint
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Usage -> IO Usage
forall (m :: * -> *) a. Monad m => a -> m a
return UsageMergedRequirement :: Module -> Fingerprint -> Usage
UsageMergedRequirement { usg_mod :: Module
usg_mod = Module
mod, usg_mod_hash :: Fingerprint
usg_mod_hash = Fingerprint
hash }
          i :: Word8
i -> String -> IO Usage
forall a. HasCallStack => String -> a
error ("Binary.get(Usage): " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Word8 -> String
forall a. Show a => a -> String
show Word8
i)
type PackageTypeEnv          = TypeEnv
type PackageRuleBase         = RuleBase
type PackageInstEnv          = InstEnv
type PackageFamInstEnv       = FamInstEnv
type PackageAnnEnv           = AnnEnv
type PackageCompleteMatchMap = CompleteMatchMap
data ExternalPackageState
  = EPS {
        ExternalPackageState -> ModuleNameEnv (ModuleName, Bool)
eps_is_boot :: !(ModuleNameEnv (ModuleName, IsBootInterface)),
                
                
                
                
                
                
                
                
                
                
                
        ExternalPackageState -> PackageIfaceTable
eps_PIT :: !PackageIfaceTable,
                
                
                
                
                
                
                
                
                
                
                
                
                
                
                
                
                
                
        ExternalPackageState -> InstalledModuleEnv (UniqDSet ModuleName)
eps_free_holes :: InstalledModuleEnv (UniqDSet ModuleName),
                
                
                
                
                
                
                
                
        ExternalPackageState -> TypeEnv
eps_PTE :: !PackageTypeEnv,
                
                
                
        ExternalPackageState -> InstEnv
eps_inst_env     :: !PackageInstEnv,   
                                               
        ExternalPackageState -> FamInstEnv
eps_fam_inst_env :: !PackageFamInstEnv,
                                               
        ExternalPackageState -> PackageRuleBase
eps_rule_base    :: !PackageRuleBase,  
                                               
        ExternalPackageState -> AnnEnv
eps_ann_env      :: !PackageAnnEnv,    
                                               
        ExternalPackageState -> PackageCompleteMatchMap
eps_complete_matches :: !PackageCompleteMatchMap,
                                  
                                  
        ExternalPackageState -> ModuleEnv FamInstEnv
eps_mod_fam_inst_env :: !(ModuleEnv FamInstEnv), 
                                                         
        ExternalPackageState -> EpsStats
eps_stats :: !EpsStats                 
  }
data EpsStats = EpsStats { EpsStats -> Int
n_ifaces_in
                         , EpsStats -> Int
n_decls_in, EpsStats -> Int
n_decls_out
                         , EpsStats -> Int
n_rules_in, EpsStats -> Int
n_rules_out
                         , EpsStats -> Int
n_insts_in, EpsStats -> Int
n_insts_out :: !Int }
addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats
addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats
addEpsInStats stats :: EpsStats
stats n_decls :: Int
n_decls n_insts :: Int
n_insts n_rules :: Int
n_rules
  = EpsStats
stats { n_ifaces_in :: Int
n_ifaces_in = EpsStats -> Int
n_ifaces_in EpsStats
stats Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 1
          , n_decls_in :: Int
n_decls_in  = EpsStats -> Int
n_decls_in EpsStats
stats Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n_decls
          , n_insts_in :: Int
n_insts_in  = EpsStats -> Int
n_insts_in EpsStats
stats Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n_insts
          , n_rules_in :: Int
n_rules_in  = EpsStats -> Int
n_rules_in EpsStats
stats Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n_rules }
updNameCache :: IORef NameCache
             -> (NameCache -> (NameCache, c))  
             -> IO c
updNameCache :: IORef NameCache -> (NameCache -> (NameCache, c)) -> IO c
updNameCache ncRef :: IORef NameCache
ncRef upd_fn :: NameCache -> (NameCache, c)
upd_fn
  = IORef NameCache -> (NameCache -> (NameCache, c)) -> IO c
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef NameCache
ncRef NameCache -> (NameCache, c)
upd_fn
mkSOName :: Platform -> FilePath -> FilePath
mkSOName :: Platform -> ShowS
mkSOName platform :: Platform
platform root :: String
root
    = case Platform -> OS
platformOS Platform
platform of
      OSMinGW32 ->           String
root  String -> ShowS
<.> Platform -> String
soExt Platform
platform
      _         -> ("lib" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
root) String -> ShowS
<.> Platform -> String
soExt Platform
platform
mkHsSOName :: Platform -> FilePath -> FilePath
mkHsSOName :: Platform -> ShowS
mkHsSOName platform :: Platform
platform root :: String
root = ("lib" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
root) String -> ShowS
<.> Platform -> String
soExt Platform
platform
soExt :: Platform -> FilePath
soExt :: Platform -> String
soExt platform :: Platform
platform
    = case Platform -> OS
platformOS Platform
platform of
      OSDarwin  -> "dylib"
      OSMinGW32 -> "dll"
      _         -> "so"
data ModuleGraph = ModuleGraph
  { ModuleGraph -> [ModSummary]
mg_mss :: [ModSummary]
  , ModuleGraph -> ModuleEnv ModSummary
mg_non_boot :: ModuleEnv ModSummary
    
  , ModuleGraph -> ModuleSet
mg_boot :: ModuleSet
    
  , ModuleGraph -> Bool
mg_needs_th_or_qq :: !Bool
    
    
  }
needsTemplateHaskellOrQQ :: ModuleGraph -> Bool
needsTemplateHaskellOrQQ :: ModuleGraph -> Bool
needsTemplateHaskellOrQQ mg :: ModuleGraph
mg = ModuleGraph -> Bool
mg_needs_th_or_qq ModuleGraph
mg
mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph
mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph
mapMG f :: ModSummary -> ModSummary
f mg :: ModuleGraph
mg@ModuleGraph{..} = ModuleGraph
mg
  { mg_mss :: [ModSummary]
mg_mss = (ModSummary -> ModSummary) -> [ModSummary] -> [ModSummary]
forall a b. (a -> b) -> [a] -> [b]
map ModSummary -> ModSummary
f [ModSummary]
mg_mss
  , mg_non_boot :: ModuleEnv ModSummary
mg_non_boot = (ModSummary -> ModSummary)
-> ModuleEnv ModSummary -> ModuleEnv ModSummary
forall a b. (a -> b) -> ModuleEnv a -> ModuleEnv b
mapModuleEnv ModSummary -> ModSummary
f ModuleEnv ModSummary
mg_non_boot
  }
mgBootModules :: ModuleGraph -> ModuleSet
mgBootModules :: ModuleGraph -> ModuleSet
mgBootModules ModuleGraph{..} = ModuleSet
mg_boot
mgModSummaries :: ModuleGraph -> [ModSummary]
mgModSummaries :: ModuleGraph -> [ModSummary]
mgModSummaries = ModuleGraph -> [ModSummary]
mg_mss
mgElemModule :: ModuleGraph -> Module -> Bool
mgElemModule :: ModuleGraph -> Module -> Bool
mgElemModule ModuleGraph{..} m :: Module
m = Module -> ModuleEnv ModSummary -> Bool
forall a. Module -> ModuleEnv a -> Bool
elemModuleEnv Module
m ModuleEnv ModSummary
mg_non_boot
mgLookupModule :: ModuleGraph -> Module -> Maybe ModSummary
mgLookupModule :: ModuleGraph -> Module -> Maybe ModSummary
mgLookupModule ModuleGraph{..} m :: Module
m = ModuleEnv ModSummary -> Module -> Maybe ModSummary
forall a. ModuleEnv a -> Module -> Maybe a
lookupModuleEnv ModuleEnv ModSummary
mg_non_boot Module
m
emptyMG :: ModuleGraph
emptyMG :: ModuleGraph
emptyMG = [ModSummary]
-> ModuleEnv ModSummary -> ModuleSet -> Bool -> ModuleGraph
ModuleGraph [] ModuleEnv ModSummary
forall a. ModuleEnv a
emptyModuleEnv ModuleSet
emptyModuleSet Bool
False
isTemplateHaskellOrQQNonBoot :: ModSummary -> Bool
isTemplateHaskellOrQQNonBoot :: ModSummary -> Bool
isTemplateHaskellOrQQNonBoot ms :: ModSummary
ms =
  (Extension -> DynFlags -> Bool
xopt Extension
LangExt.TemplateHaskell (ModSummary -> DynFlags
ms_hspp_opts ModSummary
ms)
    Bool -> Bool -> Bool
|| Extension -> DynFlags -> Bool
xopt Extension
LangExt.QuasiQuotes (ModSummary -> DynFlags
ms_hspp_opts ModSummary
ms)) Bool -> Bool -> Bool
&&
  Bool -> Bool
not (ModSummary -> Bool
isBootSummary ModSummary
ms)
extendMG :: ModuleGraph -> ModSummary -> ModuleGraph
extendMG :: ModuleGraph -> ModSummary -> ModuleGraph
extendMG ModuleGraph{..} ms :: ModSummary
ms = $WModuleGraph :: [ModSummary]
-> ModuleEnv ModSummary -> ModuleSet -> Bool -> ModuleGraph
ModuleGraph
  { mg_mss :: [ModSummary]
mg_mss = ModSummary
msModSummary -> [ModSummary] -> [ModSummary]
forall a. a -> [a] -> [a]
:[ModSummary]
mg_mss
  , mg_non_boot :: ModuleEnv ModSummary
mg_non_boot = if ModSummary -> Bool
isBootSummary ModSummary
ms
      then ModuleEnv ModSummary
mg_non_boot
      else ModuleEnv ModSummary
-> Module -> ModSummary -> ModuleEnv ModSummary
forall a. ModuleEnv a -> Module -> a -> ModuleEnv a
extendModuleEnv ModuleEnv ModSummary
mg_non_boot (ModSummary -> Module
ms_mod ModSummary
ms) ModSummary
ms
  , mg_boot :: ModuleSet
mg_boot = if ModSummary -> Bool
isBootSummary ModSummary
ms
      then ModuleSet -> Module -> ModuleSet
extendModuleSet ModuleSet
mg_boot (ModSummary -> Module
ms_mod ModSummary
ms)
      else ModuleSet
mg_boot
  , mg_needs_th_or_qq :: Bool
mg_needs_th_or_qq = Bool
mg_needs_th_or_qq Bool -> Bool -> Bool
|| ModSummary -> Bool
isTemplateHaskellOrQQNonBoot ModSummary
ms
  }
mkModuleGraph :: [ModSummary] -> ModuleGraph
mkModuleGraph :: [ModSummary] -> ModuleGraph
mkModuleGraph = (ModSummary -> ModuleGraph -> ModuleGraph)
-> ModuleGraph -> [ModSummary] -> ModuleGraph
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ((ModuleGraph -> ModSummary -> ModuleGraph)
-> ModSummary -> ModuleGraph -> ModuleGraph
forall a b c. (a -> b -> c) -> b -> a -> c
flip ModuleGraph -> ModSummary -> ModuleGraph
extendMG) ModuleGraph
emptyMG
data ModSummary
   = ModSummary {
        ModSummary -> Module
ms_mod          :: Module,
          
        ModSummary -> HscSource
ms_hsc_src      :: HscSource,
          
        ModSummary -> ModLocation
ms_location     :: ModLocation,
          
        ModSummary -> UTCTime
ms_hs_date      :: UTCTime,
          
        ModSummary -> Maybe UTCTime
ms_obj_date     :: Maybe UTCTime,
          
        ModSummary -> Maybe UTCTime
ms_iface_date   :: Maybe UTCTime,
          
          
          
        ModSummary -> Maybe UTCTime
ms_hie_date   :: Maybe UTCTime,
          
        ModSummary -> [(Maybe FastString, Located ModuleName)]
ms_srcimps      :: [(Maybe FastString, Located ModuleName)],
          
        ModSummary -> [(Maybe FastString, Located ModuleName)]
ms_textual_imps :: [(Maybe FastString, Located ModuleName)],
          
        ModSummary -> Maybe HsParsedModule
ms_parsed_mod   :: Maybe HsParsedModule,
          
          
        ModSummary -> String
ms_hspp_file    :: FilePath,
          
        ModSummary -> DynFlags
ms_hspp_opts    :: DynFlags,
          
          
        ModSummary -> Maybe InputFileBuffer
ms_hspp_buf     :: Maybe StringBuffer
          
     }
ms_installed_mod :: ModSummary -> InstalledModule
ms_installed_mod :: ModSummary -> InstalledModule
ms_installed_mod = (InstalledModule, Maybe IndefModule) -> InstalledModule
forall a b. (a, b) -> a
fst ((InstalledModule, Maybe IndefModule) -> InstalledModule)
-> (ModSummary -> (InstalledModule, Maybe IndefModule))
-> ModSummary
-> InstalledModule
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Module -> (InstalledModule, Maybe IndefModule)
splitModuleInsts (Module -> (InstalledModule, Maybe IndefModule))
-> (ModSummary -> Module)
-> ModSummary
-> (InstalledModule, Maybe IndefModule)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModSummary -> Module
ms_mod
ms_mod_name :: ModSummary -> ModuleName
ms_mod_name :: ModSummary -> ModuleName
ms_mod_name = Module -> ModuleName
moduleName (Module -> ModuleName)
-> (ModSummary -> Module) -> ModSummary -> ModuleName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModSummary -> Module
ms_mod
ms_imps :: ModSummary -> [(Maybe FastString, Located ModuleName)]
ms_imps :: ModSummary -> [(Maybe FastString, Located ModuleName)]
ms_imps ms :: ModSummary
ms =
  ModSummary -> [(Maybe FastString, Located ModuleName)]
ms_textual_imps ModSummary
ms [(Maybe FastString, Located ModuleName)]
-> [(Maybe FastString, Located ModuleName)]
-> [(Maybe FastString, Located ModuleName)]
forall a. [a] -> [a] -> [a]
++
  (ModuleName -> (Maybe FastString, Located ModuleName))
-> [ModuleName] -> [(Maybe FastString, Located ModuleName)]
forall a b. (a -> b) -> [a] -> [b]
map ModuleName -> (Maybe FastString, Located ModuleName)
forall b a. HasSrcSpan b => SrcSpanLess b -> (Maybe a, b)
mk_additional_import (DynFlags -> [ModuleName]
dynFlagDependencies (ModSummary -> DynFlags
ms_hspp_opts ModSummary
ms))
  where
    mk_additional_import :: SrcSpanLess b -> (Maybe a, b)
mk_additional_import mod_nm :: SrcSpanLess b
mod_nm = (Maybe a
forall a. Maybe a
Nothing, SrcSpanLess b -> b
forall a. HasSrcSpan a => SrcSpanLess a -> a
noLoc SrcSpanLess b
mod_nm)
msHsFilePath, msHiFilePath, msObjFilePath :: ModSummary -> FilePath
msHsFilePath :: ModSummary -> String
msHsFilePath  ms :: ModSummary
ms = String -> Maybe String -> String
forall a. HasCallStack => String -> Maybe a -> a
expectJust "msHsFilePath" (ModLocation -> Maybe String
ml_hs_file  (ModSummary -> ModLocation
ms_location ModSummary
ms))
msHiFilePath :: ModSummary -> String
msHiFilePath  ms :: ModSummary
ms = ModLocation -> String
ml_hi_file  (ModSummary -> ModLocation
ms_location ModSummary
ms)
msObjFilePath :: ModSummary -> String
msObjFilePath ms :: ModSummary
ms = ModLocation -> String
ml_obj_file (ModSummary -> ModLocation
ms_location ModSummary
ms)
isBootSummary :: ModSummary -> Bool
isBootSummary :: ModSummary -> Bool
isBootSummary ms :: ModSummary
ms = ModSummary -> HscSource
ms_hsc_src ModSummary
ms HscSource -> HscSource -> Bool
forall a. Eq a => a -> a -> Bool
== HscSource
HsBootFile
instance Outputable ModSummary where
   ppr :: ModSummary -> SDoc
ppr ms :: ModSummary
ms
      = [SDoc] -> SDoc
sep [String -> SDoc
text "ModSummary {",
             Int -> SDoc -> SDoc
nest 3 ([SDoc] -> SDoc
sep [String -> SDoc
text "ms_hs_date = " SDoc -> SDoc -> SDoc
<> String -> SDoc
text (UTCTime -> String
forall a. Show a => a -> String
show (ModSummary -> UTCTime
ms_hs_date ModSummary
ms)),
                          String -> SDoc
text "ms_mod =" SDoc -> SDoc -> SDoc
<+> Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr (ModSummary -> Module
ms_mod ModSummary
ms)
                                SDoc -> SDoc -> SDoc
<> String -> SDoc
text (HscSource -> String
hscSourceString (ModSummary -> HscSource
ms_hsc_src ModSummary
ms)) SDoc -> SDoc -> SDoc
<> SDoc
comma,
                          String -> SDoc
text "ms_textual_imps =" SDoc -> SDoc -> SDoc
<+> [(Maybe FastString, Located ModuleName)] -> SDoc
forall a. Outputable a => a -> SDoc
ppr (ModSummary -> [(Maybe FastString, Located ModuleName)]
ms_textual_imps ModSummary
ms),
                          String -> SDoc
text "ms_srcimps =" SDoc -> SDoc -> SDoc
<+> [(Maybe FastString, Located ModuleName)] -> SDoc
forall a. Outputable a => a -> SDoc
ppr (ModSummary -> [(Maybe FastString, Located ModuleName)]
ms_srcimps ModSummary
ms)]),
             Char -> SDoc
char '}'
            ]
showModMsg :: DynFlags -> HscTarget -> Bool -> ModSummary -> String
showModMsg :: DynFlags -> HscTarget -> Bool -> ModSummary -> String
showModMsg dflags :: DynFlags
dflags target :: HscTarget
target recomp :: Bool
recomp mod_summary :: ModSummary
mod_summary = DynFlags -> SDoc -> String
showSDoc DynFlags
dflags (SDoc -> String) -> SDoc -> String
forall a b. (a -> b) -> a -> b
$
   if GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_HideSourcePaths DynFlags
dflags
      then String -> SDoc
text String
mod_str
      else [SDoc] -> SDoc
hsep
         [ String -> SDoc
text (String
mod_str String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> Char -> String
forall a. Int -> a -> [a]
replicate (Int -> Int -> Int
forall a. Ord a => a -> a -> a
max 0 (16 Int -> Int -> Int
forall a. Num a => a -> a -> a
- String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
mod_str)) ' ')
         , Char -> SDoc
char '('
         , String -> SDoc
text (ShowS
op ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ ModSummary -> String
msHsFilePath ModSummary
mod_summary) SDoc -> SDoc -> SDoc
<> Char -> SDoc
char ','
         , case HscTarget
target of
              HscInterpreted | Bool
recomp -> String -> SDoc
text "interpreted"
              HscNothing              -> String -> SDoc
text "nothing"
              _                       -> String -> SDoc
text (ShowS
op ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ ModSummary -> String
msObjFilePath ModSummary
mod_summary)
         , Char -> SDoc
char ')'
         ]
  where
    op :: ShowS
op      = ShowS
normalise
    mod :: ModuleName
mod     = Module -> ModuleName
moduleName (ModSummary -> Module
ms_mod ModSummary
mod_summary)
    mod_str :: String
mod_str = DynFlags -> ModuleName -> String
forall a. Outputable a => DynFlags -> a -> String
showPpr DynFlags
dflags ModuleName
mod String -> ShowS
forall a. [a] -> [a] -> [a]
++ HscSource -> String
hscSourceString (ModSummary -> HscSource
ms_hsc_src ModSummary
mod_summary)
data SourceModified
  = SourceModified
       
  | SourceUnmodified
       
       
       
  | SourceUnmodifiedAndStable
       
       
       
       
       
       
data HpcInfo
  = HpcInfo
     { HpcInfo -> Int
hpcInfoTickCount :: Int
     , HpcInfo -> Int
hpcInfoHash      :: Int
     }
  | NoHpcInfo
     { HpcInfo -> Bool
hpcUsed          :: AnyHpcUsage  
     }
type AnyHpcUsage = Bool
emptyHpcInfo :: AnyHpcUsage -> HpcInfo
emptyHpcInfo :: Bool -> HpcInfo
emptyHpcInfo = Bool -> HpcInfo
NoHpcInfo
isHpcUsed :: HpcInfo -> AnyHpcUsage
isHpcUsed :: HpcInfo -> Bool
isHpcUsed (HpcInfo {})                   = Bool
True
isHpcUsed (NoHpcInfo { hpcUsed :: HpcInfo -> Bool
hpcUsed = Bool
used }) = Bool
used
type IsSafeImport = Bool
newtype IfaceTrustInfo = TrustInfo SafeHaskellMode
getSafeMode :: IfaceTrustInfo -> SafeHaskellMode
getSafeMode :: IfaceTrustInfo -> SafeHaskellMode
getSafeMode (TrustInfo x :: SafeHaskellMode
x) = SafeHaskellMode
x
setSafeMode :: SafeHaskellMode -> IfaceTrustInfo
setSafeMode :: SafeHaskellMode -> IfaceTrustInfo
setSafeMode = SafeHaskellMode -> IfaceTrustInfo
TrustInfo
noIfaceTrustInfo :: IfaceTrustInfo
noIfaceTrustInfo :: IfaceTrustInfo
noIfaceTrustInfo = SafeHaskellMode -> IfaceTrustInfo
setSafeMode SafeHaskellMode
Sf_None
trustInfoToNum :: IfaceTrustInfo -> Word8
trustInfoToNum :: IfaceTrustInfo -> Word8
trustInfoToNum it :: IfaceTrustInfo
it
  = case IfaceTrustInfo -> SafeHaskellMode
getSafeMode IfaceTrustInfo
it of
            Sf_None         -> 0
            Sf_Unsafe       -> 1
            Sf_Trustworthy  -> 2
            Sf_Safe         -> 3
            Sf_Ignore       -> 0
numToTrustInfo :: Word8 -> IfaceTrustInfo
numToTrustInfo :: Word8 -> IfaceTrustInfo
numToTrustInfo 0 = SafeHaskellMode -> IfaceTrustInfo
setSafeMode SafeHaskellMode
Sf_None
numToTrustInfo 1 = SafeHaskellMode -> IfaceTrustInfo
setSafeMode SafeHaskellMode
Sf_Unsafe
numToTrustInfo 2 = SafeHaskellMode -> IfaceTrustInfo
setSafeMode SafeHaskellMode
Sf_Trustworthy
numToTrustInfo 3 = SafeHaskellMode -> IfaceTrustInfo
setSafeMode SafeHaskellMode
Sf_Safe
numToTrustInfo 4 = SafeHaskellMode -> IfaceTrustInfo
setSafeMode SafeHaskellMode
Sf_Safe 
                                       
                                       
numToTrustInfo n :: Word8
n = String -> IfaceTrustInfo
forall a. HasCallStack => String -> a
error (String -> IfaceTrustInfo) -> String -> IfaceTrustInfo
forall a b. (a -> b) -> a -> b
$ "numToTrustInfo: bad input number! (" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Word8 -> String
forall a. Show a => a -> String
show Word8
n String -> ShowS
forall a. [a] -> [a] -> [a]
++ ")"
instance Outputable IfaceTrustInfo where
    ppr :: IfaceTrustInfo -> SDoc
ppr (TrustInfo Sf_None)          = String -> SDoc
text "none"
    ppr (TrustInfo Sf_Ignore)        = String -> SDoc
text "none"
    ppr (TrustInfo Sf_Unsafe)        = String -> SDoc
text "unsafe"
    ppr (TrustInfo Sf_Trustworthy)   = String -> SDoc
text "trustworthy"
    ppr (TrustInfo Sf_Safe)          = String -> SDoc
text "safe"
instance Binary IfaceTrustInfo where
    put_ :: BinHandle -> IfaceTrustInfo -> IO ()
put_ bh :: BinHandle
bh iftrust :: IfaceTrustInfo
iftrust = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh (Word8 -> IO ()) -> Word8 -> IO ()
forall a b. (a -> b) -> a -> b
$ IfaceTrustInfo -> Word8
trustInfoToNum IfaceTrustInfo
iftrust
    get :: BinHandle -> IO IfaceTrustInfo
get bh :: BinHandle
bh = BinHandle -> IO Word8
getByte BinHandle
bh IO Word8 -> (Word8 -> IO IfaceTrustInfo) -> IO IfaceTrustInfo
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (IfaceTrustInfo -> IO IfaceTrustInfo
forall (m :: * -> *) a. Monad m => a -> m a
return (IfaceTrustInfo -> IO IfaceTrustInfo)
-> (Word8 -> IfaceTrustInfo) -> Word8 -> IO IfaceTrustInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> IfaceTrustInfo
numToTrustInfo)
data HsParsedModule = HsParsedModule {
    HsParsedModule -> Located (HsModule GhcPs)
hpm_module    :: Located (HsModule GhcPs),
    HsParsedModule -> [String]
hpm_src_files :: [FilePath],
       
       
       
       
       
    HsParsedModule -> ApiAnns
hpm_annotations :: ApiAnns
    
  }
data Linkable = LM {
  Linkable -> UTCTime
linkableTime     :: UTCTime,          
                                        
                                        
  Linkable -> Module
linkableModule   :: Module,           
  Linkable -> [Unlinked]
linkableUnlinked :: [Unlinked]
    
    
    
    
    
    
    
 }
isObjectLinkable :: Linkable -> Bool
isObjectLinkable :: Linkable -> Bool
isObjectLinkable l :: Linkable
l = Bool -> Bool
not ([Unlinked] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Unlinked]
unlinked) Bool -> Bool -> Bool
&& (Unlinked -> Bool) -> [Unlinked] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Unlinked -> Bool
isObject [Unlinked]
unlinked
  where unlinked :: [Unlinked]
unlinked = Linkable -> [Unlinked]
linkableUnlinked Linkable
l
        
        
        
        
linkableObjs :: Linkable -> [FilePath]
linkableObjs :: Linkable -> [String]
linkableObjs l :: Linkable
l = [ String
f | DotO f :: String
f <- Linkable -> [Unlinked]
linkableUnlinked Linkable
l ]
instance Outputable Linkable where
   ppr :: Linkable -> SDoc
ppr (LM when_made :: UTCTime
when_made mod :: Module
mod unlinkeds :: [Unlinked]
unlinkeds)
      = (String -> SDoc
text "LinkableM" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
parens (String -> SDoc
text (UTCTime -> String
forall a. Show a => a -> String
show UTCTime
when_made)) SDoc -> SDoc -> SDoc
<+> Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr Module
mod)
        SDoc -> SDoc -> SDoc
$$ Int -> SDoc -> SDoc
nest 3 ([Unlinked] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Unlinked]
unlinkeds)
data Unlinked
   = DotO FilePath      
   | DotA FilePath      
   | DotDLL FilePath    
   | BCOs CompiledByteCode
          [SptEntry]    
                        
                        
                        
                        
instance Outputable Unlinked where
   ppr :: Unlinked -> SDoc
ppr (DotO path :: String
path)   = String -> SDoc
text "DotO" SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
path
   ppr (DotA path :: String
path)   = String -> SDoc
text "DotA" SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
path
   ppr (DotDLL path :: String
path) = String -> SDoc
text "DotDLL" SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
path
   ppr (BCOs bcos :: CompiledByteCode
bcos spt :: [SptEntry]
spt) = String -> SDoc
text "BCOs" SDoc -> SDoc -> SDoc
<+> CompiledByteCode -> SDoc
forall a. Outputable a => a -> SDoc
ppr CompiledByteCode
bcos SDoc -> SDoc -> SDoc
<+> [SptEntry] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [SptEntry]
spt
isObject :: Unlinked -> Bool
isObject :: Unlinked -> Bool
isObject (DotO _)   = Bool
True
isObject (DotA _)   = Bool
True
isObject (DotDLL _) = Bool
True
isObject _          = Bool
False
isInterpretable :: Unlinked -> Bool
isInterpretable :: Unlinked -> Bool
isInterpretable = Bool -> Bool
not (Bool -> Bool) -> (Unlinked -> Bool) -> Unlinked -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unlinked -> Bool
isObject
nameOfObject :: Unlinked -> FilePath
nameOfObject :: Unlinked -> String
nameOfObject (DotO fn :: String
fn)   = String
fn
nameOfObject (DotA fn :: String
fn)   = String
fn
nameOfObject (DotDLL fn :: String
fn) = String
fn
nameOfObject other :: Unlinked
other       = String -> SDoc -> String
forall a. HasCallStack => String -> SDoc -> a
pprPanic "nameOfObject" (Unlinked -> SDoc
forall a. Outputable a => a -> SDoc
ppr Unlinked
other)
byteCodeOfObject :: Unlinked -> CompiledByteCode
byteCodeOfObject :: Unlinked -> CompiledByteCode
byteCodeOfObject (BCOs bc :: CompiledByteCode
bc _) = CompiledByteCode
bc
byteCodeOfObject other :: Unlinked
other       = String -> SDoc -> CompiledByteCode
forall a. HasCallStack => String -> SDoc -> a
pprPanic "byteCodeOfObject" (Unlinked -> SDoc
forall a. Outputable a => a -> SDoc
ppr Unlinked
other)
data CompleteMatch = CompleteMatch {
                            CompleteMatch -> [Name]
completeMatchConLikes :: [Name]
                            
                            
                          , CompleteMatch -> Name
completeMatchTyCon :: Name
                            
                          }
instance Outputable CompleteMatch where
  ppr :: CompleteMatch -> SDoc
ppr (CompleteMatch cl :: [Name]
cl ty :: Name
ty) = String -> SDoc
text "CompleteMatch:" SDoc -> SDoc -> SDoc
<+> [Name] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Name]
cl
                                                    SDoc -> SDoc -> SDoc
<+> SDoc
dcolon SDoc -> SDoc -> SDoc
<+> Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
ty
type CompleteMatchMap = UniqFM [CompleteMatch]
mkCompleteMatchMap :: [CompleteMatch] -> CompleteMatchMap
mkCompleteMatchMap :: [CompleteMatch] -> PackageCompleteMatchMap
mkCompleteMatchMap = PackageCompleteMatchMap
-> [CompleteMatch] -> PackageCompleteMatchMap
extendCompleteMatchMap PackageCompleteMatchMap
forall a. NameEnv a
emptyUFM
extendCompleteMatchMap :: CompleteMatchMap -> [CompleteMatch]
                       -> CompleteMatchMap
extendCompleteMatchMap :: PackageCompleteMatchMap
-> [CompleteMatch] -> PackageCompleteMatchMap
extendCompleteMatchMap = (PackageCompleteMatchMap
 -> CompleteMatch -> PackageCompleteMatchMap)
-> PackageCompleteMatchMap
-> [CompleteMatch]
-> PackageCompleteMatchMap
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' PackageCompleteMatchMap -> CompleteMatch -> PackageCompleteMatchMap
insertMatch
  where
    insertMatch :: CompleteMatchMap -> CompleteMatch -> CompleteMatchMap
    insertMatch :: PackageCompleteMatchMap -> CompleteMatch -> PackageCompleteMatchMap
insertMatch ufm :: PackageCompleteMatchMap
ufm c :: CompleteMatch
c@(CompleteMatch _ t :: Name
t) = ([CompleteMatch] -> [CompleteMatch] -> [CompleteMatch])
-> PackageCompleteMatchMap
-> Name
-> [CompleteMatch]
-> PackageCompleteMatchMap
forall key elt.
Uniquable key =>
(elt -> elt -> elt) -> UniqFM elt -> key -> elt -> UniqFM elt
addToUFM_C [CompleteMatch] -> [CompleteMatch] -> [CompleteMatch]
forall a. [a] -> [a] -> [a]
(++) PackageCompleteMatchMap
ufm Name
t [CompleteMatch
c]