{-# LANGUAGE CPP, NondecreasingIndentation, ScopedTypeVariables #-}
{-# LANGUAGE TupleSections, NamedFieldPuns #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE TypeFamilies #-}
module GHC (
defaultErrorHandler,
defaultCleanupHandler,
prettyPrintGhcErrors,
withSignalHandlers,
withCleanupSession,
Ghc, GhcT, GhcMonad(..), HscEnv,
runGhc, runGhcT, initGhcMonad,
printException,
handleSourceError,
needsTemplateHaskellOrQQ,
DynFlags(..), GeneralFlag(..), Severity(..), HscTarget(..), gopt,
GhcMode(..), GhcLink(..), defaultObjectTarget,
parseDynamicFlags,
getSessionDynFlags, setSessionDynFlags,
getProgramDynFlags, setProgramDynFlags, setLogAction,
getInteractiveDynFlags, setInteractiveDynFlags,
interpretPackageEnv,
Target(..), TargetId(..), Phase,
setTargets,
getTargets,
addTarget,
removeTarget,
guessTarget,
depanal, depanalE,
load, LoadHowMuch(..), InteractiveImport(..),
SuccessFlag(..), succeeded, failed,
defaultWarnErrLogger, WarnErrLogger,
workingDirectoryChanged,
parseModule, typecheckModule, desugarModule, loadModule,
ParsedModule(..), TypecheckedModule(..), DesugaredModule(..),
TypecheckedSource, ParsedSource, RenamedSource,
TypecheckedMod, ParsedMod,
moduleInfo, renamedSource, typecheckedSource,
parsedSource, coreModule,
CoreModule(..),
compileToCoreModule, compileToCoreSimplified,
ModuleGraph, emptyMG, mapMG, mkModuleGraph, mgModSummaries,
mgLookupModule,
ModSummary(..), ms_mod_name, ModLocation(..),
getModSummary,
getModuleGraph,
isLoaded,
topSortModuleGraph,
ModuleInfo,
getModuleInfo,
modInfoTyThings,
modInfoTopLevelScope,
modInfoExports,
modInfoExportsWithSelectors,
modInfoInstances,
modInfoIsExportedName,
modInfoLookupName,
modInfoIface,
modInfoRdrEnv,
modInfoSafe,
lookupGlobalName,
findGlobalAnns,
mkPrintUnqualifiedForModule,
ModIface, ModIface_(..),
SafeHaskellMode(..),
PrintUnqualified, alwaysQualify,
execStmt, execStmt', ExecOptions(..), execOptions, ExecResult(..),
resumeExec,
runDecls, runDeclsWithLocation, runParsedDecls,
parseImportDecl,
setContext, getContext,
setGHCiMonad, getGHCiMonad,
getBindings, getInsts, getPrintUnqual,
findModule, lookupModule,
isModuleTrusted, moduleTrustReqs,
getNamesInScope,
getRdrNamesInScope,
getGRE,
moduleIsInterpreted,
getInfo,
showModule,
moduleIsBootOrNotObjectLinkable,
getNameToInstancesIndex,
exprType, TcRnExprMode(..),
typeKind,
parseName,
lookupName,
HValue, parseExpr, compileParsedExpr,
GHC.Runtime.Eval.compileExpr, dynCompileExpr,
ForeignHValue,
compileExprRemote, compileParsedExprRemote,
getDocs, GetDocsFailure(..),
runTcInteractive,
isStmt, hasImport, isImport, isDecl,
SingleStep(..),
Resume(..),
History(historyBreakInfo, historyEnclosingDecls),
GHC.getHistorySpan, getHistoryModule,
abandon, abandonAll,
getResumeContext,
GHC.obtainTermFromId, GHC.obtainTermFromVal, reconstructType,
modInfoModBreaks,
ModBreaks(..), BreakIndex,
BreakInfo(breakInfo_number, breakInfo_module),
GHC.Runtime.Eval.back,
GHC.Runtime.Eval.forward,
Unit,
Module, mkModule, pprModule, moduleName, moduleUnit,
ModuleName, mkModuleName, moduleNameString,
Name,
isExternalName, nameModule, pprParenSymName, nameSrcSpan,
NamedThing(..),
RdrName(Qual,Unqual),
Id, idType,
isImplicitId, isDeadBinder,
isExportedId, isLocalId, isGlobalId,
isRecordSelector,
isPrimOpId, isFCallId, isClassOpId_maybe,
isDataConWorkId, idDataCon,
isDeadEndId, isDictonaryId,
recordSelectorTyCon,
TyCon,
tyConTyVars, tyConDataCons, tyConArity,
isClassTyCon, isTypeSynonymTyCon, isTypeFamilyTyCon, isNewTyCon,
isPrimTyCon, isFunTyCon,
isFamilyTyCon, isOpenFamilyTyCon, isOpenTypeFamilyTyCon,
tyConClass_maybe,
synTyConRhs_maybe, synTyConDefn_maybe, tyConKind,
TyVar,
alphaTyVars,
DataCon,
dataConType, dataConTyCon, dataConFieldLabels,
dataConIsInfix, isVanillaDataCon, dataConUserType,
dataConSrcBangs,
StrictnessMark(..), isMarkedStrict,
Class,
classMethods, classSCTheta, classTvsFds, classATs,
pprFundeps,
ClsInst,
instanceDFunId,
pprInstance, pprInstanceHdr,
pprFamInst,
FamInst,
Type, splitForAllTys, funResultTy,
pprParendType, pprTypeApp,
Kind,
PredType,
ThetaType, pprForAll, pprThetaArrowTy,
parseInstanceHead,
getInstancesForType,
TyThing(..),
module GHC.Hs,
FixityDirection(..),
defaultFixity, maxPrecedence,
negateFixity,
compareFixity,
LexicalFixity(..),
SrcLoc(..), RealSrcLoc,
mkSrcLoc, noSrcLoc,
srcLocFile, srcLocLine, srcLocCol,
SrcSpan(..), RealSrcSpan,
mkSrcSpan, srcLocSpan, isGoodSrcSpan, noSrcSpan,
srcSpanStart, srcSpanEnd,
srcSpanFile,
srcSpanStartLine, srcSpanEndLine,
srcSpanStartCol, srcSpanEndCol,
GenLocated(..), Located,
noLoc, mkGeneralLocated,
getLoc, unLoc,
getRealSrcSpan, unRealSrcSpan,
eqLocated, cmpLocated, combineLocs, addCLoc,
leftmost_smallest, leftmost_largest, rightmost_smallest,
spans, isSubspanOf,
GhcException(..), showGhcException,
Token,
getTokenStream, getRichTokenStream,
showRichTokenStream, addSourceToTokens,
parser,
ApiAnns(..),AnnKeywordId(..),AnnotationComment(..),
getAnnotation, getAndRemoveAnnotation,
getAnnotationComments, getAndRemoveAnnotationComments,
unicodeAnn,
cyclicModuleErr,
) where
#include "HsVersions.h"
import GHC.Prelude hiding (init)
import GHC.ByteCode.Types
import GHC.Runtime.Eval
import GHC.Runtime.Eval.Types
import GHC.Runtime.Interpreter
import GHC.Runtime.Interpreter.Types
import GHCi.RemoteTypes
import GHC.Core.Ppr.TyThing ( pprFamInst )
import GHC.Driver.Main
import GHC.Driver.Make
import GHC.Driver.Hooks
import GHC.Driver.Pipeline ( compileOne' )
import GHC.Driver.Monad
import GHC.Tc.Utils.Monad ( finalSafeMode, fixSafeInstances, initIfaceTcRn )
import GHC.Iface.Load ( loadSysInterface )
import GHC.Tc.Types
import GHC.Core.Predicate
import GHC.Unit.State
import GHC.Types.Name.Set
import GHC.Types.Name.Reader
import GHC.Hs
import GHC.Core.Type hiding( typeKind )
import GHC.Tc.Utils.TcType
import GHC.Types.Id
import GHC.Builtin.Types.Prim ( alphaTyVars )
import GHC.Core.TyCon
import GHC.Core.TyCo.Ppr ( pprForAll )
import GHC.Core.Class
import GHC.Core.DataCon
import GHC.Core.FVs ( orphNamesOfFamInst )
import GHC.Core.FamInstEnv ( FamInst, famInstEnvElts )
import GHC.Core.InstEnv
import GHC.Types.Name hiding ( varName )
import GHC.Types.Avail
import GHC.Types.SrcLoc
import GHC.Core
import GHC.Iface.Tidy
import GHC.Driver.Phases ( Phase(..), isHaskellSrcFilename )
import GHC.Driver.Finder
import GHC.Driver.Types
import GHC.Driver.CmdLine
import GHC.Driver.Session hiding (WarnReason(..))
import GHC.Driver.Ways
import GHC.SysTools
import GHC.SysTools.BaseDir
import GHC.Types.Annotations
import GHC.Unit.Module
import GHC.Utils.Panic
import GHC.Platform
import GHC.Data.Bag ( listToBag )
import GHC.Utils.Error
import GHC.Utils.Monad
import GHC.Utils.Misc
import GHC.Data.StringBuffer
import GHC.Utils.Outputable
import GHC.Types.Basic
import GHC.Data.FastString
import qualified GHC.Parser as Parser
import GHC.Parser.Lexer
import GHC.Parser.Annotation
import qualified GHC.LanguageExtensions as LangExt
import GHC.Types.Name.Env
import GHC.Tc.Module
import GHC.Tc.Utils.Instantiate
import GHC.Tc.Instance.Family
import GHC.SysTools.FileCleanup
import Data.Foldable
import qualified Data.Map.Strict as Map
import Data.Set (Set)
import qualified Data.Set as S
import qualified Data.Sequence as Seq
import Data.Maybe
import Data.Time
import Data.Typeable ( Typeable )
import Data.Word ( Word8 )
import Control.Monad
import System.Exit ( exitWith, ExitCode(..) )
import GHC.Utils.Exception
import Data.IORef
import System.FilePath
import Control.Concurrent
import Control.Applicative ((<|>))
import Control.Monad.Catch as MC
import GHC.Data.Maybe
import System.IO.Error ( isDoesNotExistError )
import System.Environment ( getEnv )
import System.Directory
defaultErrorHandler :: (ExceptionMonad m)
=> FatalMessager -> FlushOut -> m a -> m a
defaultErrorHandler :: FatalMessager -> FlushOut -> m a -> m a
defaultErrorHandler FatalMessager
fm (FlushOut IO ()
flushOut) m a
inner =
(SomeException -> m a) -> m a -> m a
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
(e -> m a) -> m a -> m a
External instance of the constraint type Exception SomeException
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
Evidence bound by a type signature of the constraint type ExceptionMonad m
MC.handle (\SomeException
exception -> IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
Evidence bound by a type signature of the constraint type ExceptionMonad m
liftIO (IO a -> m a) -> IO a -> m a
forall a b. (a -> b) -> a -> b
$ do
IO ()
flushOut
case SomeException -> Maybe IOError
forall e. Exception e => SomeException -> Maybe e
External instance of the constraint type Exception IOError
fromException SomeException
exception of
Just (IOError
ioe :: IOException) ->
FatalMessager -> FatalMessager
fatalErrorMsg'' FatalMessager
fm (IOError -> FilePath
forall a. Show a => a -> FilePath
External instance of the constraint type Show IOError
show IOError
ioe)
Maybe IOError
_ -> case SomeException -> Maybe AsyncException
forall e. Exception e => SomeException -> Maybe e
External instance of the constraint type Exception AsyncException
fromException SomeException
exception of
Just AsyncException
UserInterrupt ->
IO () -> IO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO IO
liftIO (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ AsyncException -> IO ()
forall e a. Exception e => e -> IO a
External instance of the constraint type Exception AsyncException
throwIO AsyncException
UserInterrupt
Just AsyncException
StackOverflow ->
FatalMessager -> FatalMessager
fatalErrorMsg'' FatalMessager
fm FilePath
"stack overflow: use +RTS -K<size> to increase it"
Maybe AsyncException
_ -> case SomeException -> Maybe ExitCode
forall e. Exception e => SomeException -> Maybe e
External instance of the constraint type Exception ExitCode
fromException SomeException
exception of
Just (ExitCode
ex :: ExitCode) -> IO () -> IO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO IO
liftIO (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ ExitCode -> IO ()
forall e a. Exception e => e -> IO a
External instance of the constraint type Exception ExitCode
throwIO ExitCode
ex
Maybe ExitCode
_ ->
FatalMessager -> FatalMessager
fatalErrorMsg'' FatalMessager
fm
(GhcException -> FilePath
forall a. Show a => a -> FilePath
External instance of the constraint type Show GhcException
show (FilePath -> GhcException
Panic (SomeException -> FilePath
forall a. Show a => a -> FilePath
External instance of the constraint type Show SomeException
show SomeException
exception)))
ExitCode -> IO a
forall a. ExitCode -> IO a
exitWith (Int -> ExitCode
ExitFailure Int
1)
) (m a -> m a) -> m a -> m a
forall a b. (a -> b) -> a -> b
$
(GhcException -> m a) -> m a -> m a
forall (m :: * -> *) a.
ExceptionMonad m =>
(GhcException -> m a) -> m a -> m a
Evidence bound by a type signature of the constraint type ExceptionMonad m
handleGhcException
(\GhcException
ge -> IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
Evidence bound by a type signature of the constraint type ExceptionMonad m
liftIO (IO a -> m a) -> IO a -> m a
forall a b. (a -> b) -> a -> b
$ do
IO ()
flushOut
case GhcException
ge of
Signal Int
_ -> ExitCode -> IO a
forall a. ExitCode -> IO a
exitWith (Int -> ExitCode
ExitFailure Int
1)
GhcException
_ -> do FatalMessager -> FatalMessager
fatalErrorMsg'' FatalMessager
fm (GhcException -> FilePath
forall a. Show a => a -> FilePath
External instance of the constraint type Show GhcException
show GhcException
ge)
ExitCode -> IO a
forall a. ExitCode -> IO a
exitWith (Int -> ExitCode
ExitFailure Int
1)
) (m a -> m a) -> m a -> m a
forall a b. (a -> b) -> a -> b
$
m a
inner
{-# DEPRECATED defaultCleanupHandler "Cleanup is now done by runGhc/runGhcT" #-}
defaultCleanupHandler :: (ExceptionMonad m) => DynFlags -> m a -> m a
defaultCleanupHandler :: DynFlags -> m a -> m a
defaultCleanupHandler DynFlags
_ m a
m = m a
m
where _warning_suppression :: m a
_warning_suppression = m a
m m a -> m Any -> m a
forall (m :: * -> *) a b. MonadCatch m => m a -> m b -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
Evidence bound by a type signature of the constraint type ExceptionMonad m
`MC.onException` m Any
forall a. HasCallStack => a
undefined
runGhc :: Maybe FilePath
-> Ghc a
-> IO a
runGhc :: Maybe FilePath -> Ghc a -> IO a
runGhc Maybe FilePath
mb_top_dir Ghc a
ghc = do
IORef HscEnv
ref <- HscEnv -> IO (IORef HscEnv)
forall a. a -> IO (IORef a)
newIORef (FilePath -> HscEnv
forall a. FilePath -> a
panic FilePath
"empty session")
let session :: Session
session = IORef HscEnv -> Session
Session IORef HscEnv
ref
(Ghc a -> Session -> IO a) -> Session -> Ghc a -> IO a
forall a b c. (a -> b -> c) -> b -> a -> c
flip Ghc a -> Session -> IO a
forall a. Ghc a -> Session -> IO a
unGhc Session
session (Ghc a -> IO a) -> Ghc a -> IO a
forall a b. (a -> b) -> a -> b
$ Ghc a -> Ghc a
forall (m :: * -> *) a. ExceptionMonad m => m a -> m a
External instance of the constraint type MonadCatch Ghc
External instance of the constraint type MonadThrow Ghc
External instance of the constraint type MonadMask Ghc
External instance of the constraint type MonadIO Ghc
withSignalHandlers (Ghc a -> Ghc a) -> Ghc a -> Ghc a
forall a b. (a -> b) -> a -> b
$ do
Maybe FilePath -> Ghc ()
forall (m :: * -> *). GhcMonad m => Maybe FilePath -> m ()
External instance of the constraint type GhcMonad Ghc
initGhcMonad Maybe FilePath
mb_top_dir
Ghc a -> Ghc a
forall (m :: * -> *) a. GhcMonad m => m a -> m a
External instance of the constraint type GhcMonad Ghc
withCleanupSession Ghc a
ghc
runGhcT :: ExceptionMonad m =>
Maybe FilePath
-> GhcT m a
-> m a
runGhcT :: Maybe FilePath -> GhcT m a -> m a
runGhcT Maybe FilePath
mb_top_dir GhcT m a
ghct = do
IORef HscEnv
ref <- IO (IORef HscEnv) -> m (IORef HscEnv)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
Evidence bound by a type signature of the constraint type ExceptionMonad m
liftIO (IO (IORef HscEnv) -> m (IORef HscEnv))
-> IO (IORef HscEnv) -> m (IORef HscEnv)
forall a b. (a -> b) -> a -> b
$ HscEnv -> IO (IORef HscEnv)
forall a. a -> IO (IORef a)
newIORef (FilePath -> HscEnv
forall a. FilePath -> a
panic FilePath
"empty session")
let session :: Session
session = IORef HscEnv -> Session
Session IORef HscEnv
ref
(GhcT m a -> Session -> m a) -> Session -> GhcT m a -> m a
forall a b c. (a -> b -> c) -> b -> a -> c
flip GhcT m a -> Session -> m a
forall (m :: * -> *) a. GhcT m a -> Session -> m a
unGhcT Session
session (GhcT m a -> m a) -> GhcT m a -> m a
forall a b. (a -> b) -> a -> b
$ GhcT m a -> GhcT m a
forall (m :: * -> *) a. ExceptionMonad m => m a -> m a
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadCatch (GhcT m)
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
Evidence bound by a type signature of the constraint type ExceptionMonad m
External instance of the constraint type forall (m :: * -> *). MonadThrow m => MonadThrow (GhcT m)
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
Evidence bound by a type signature of the constraint type ExceptionMonad m
External instance of the constraint type forall (m :: * -> *). MonadMask m => MonadMask (GhcT m)
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c3
Evidence bound by a type signature of the constraint type ExceptionMonad m
External instance of the constraint type forall (m :: * -> *). MonadIO m => MonadIO (GhcT m)
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
Evidence bound by a type signature of the constraint type ExceptionMonad m
withSignalHandlers (GhcT m a -> GhcT m a) -> GhcT m a -> GhcT m a
forall a b. (a -> b) -> a -> b
$ do
Maybe FilePath -> GhcT m ()
forall (m :: * -> *). GhcMonad m => Maybe FilePath -> m ()
External instance of the constraint type forall (m :: * -> *). ExceptionMonad m => GhcMonad (GhcT m)
Evidence bound by a type signature of the constraint type ExceptionMonad m
initGhcMonad Maybe FilePath
mb_top_dir
GhcT m a -> GhcT m a
forall (m :: * -> *) a. GhcMonad m => m a -> m a
External instance of the constraint type forall (m :: * -> *). ExceptionMonad m => GhcMonad (GhcT m)
Evidence bound by a type signature of the constraint type ExceptionMonad m
withCleanupSession GhcT m a
ghct
withCleanupSession :: GhcMonad m => m a -> m a
withCleanupSession :: m a -> m a
withCleanupSession m a
ghc = m a
ghc m a -> m () -> m a
forall (m :: * -> *) a b. MonadMask m => m a -> m b -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c3
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
`MC.finally` m ()
cleanup
where
cleanup :: m ()
cleanup = do
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
Evidence bound by a type signature of the constraint type GhcMonad m
getSession
let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
DynFlags -> IO ()
cleanTempFiles DynFlags
dflags
DynFlags -> IO ()
cleanTempDirs DynFlags
dflags
HscEnv -> IO ()
stopInterp HscEnv
hsc_env
initGhcMonad :: GhcMonad m => Maybe FilePath -> m ()
initGhcMonad :: Maybe FilePath -> m ()
initGhcMonad Maybe FilePath
mb_top_dir
= do { HscEnv
env <- IO HscEnv -> m HscEnv
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO HscEnv -> m HscEnv) -> IO HscEnv -> m HscEnv
forall a b. (a -> b) -> a -> b
$
do { FilePath
top_dir <- Maybe FilePath -> IO FilePath
findTopDir Maybe FilePath
mb_top_dir
; Settings
mySettings <- FilePath -> IO Settings
initSysTools FilePath
top_dir
; LlvmConfig
myLlvmConfig <- FilePath -> IO LlvmConfig
lazyInitLlvmConfig FilePath
top_dir
; DynFlags
dflags <- DynFlags -> IO DynFlags
initDynFlags (Settings -> LlvmConfig -> DynFlags
defaultDynFlags Settings
mySettings LlvmConfig
myLlvmConfig)
; DynFlags -> IO ()
forall (m :: * -> *). MonadIO m => DynFlags -> m ()
External instance of the constraint type MonadIO IO
checkBrokenTablesNextToCode DynFlags
dflags
; DynFlags -> IO ()
setUnsafeGlobalDynFlags DynFlags
dflags
; DynFlags -> IO HscEnv
newHscEnv DynFlags
dflags }
; HscEnv -> m ()
forall (m :: * -> *). GhcMonad m => HscEnv -> m ()
Evidence bound by a type signature of the constraint type GhcMonad m
setSession HscEnv
env }
checkBrokenTablesNextToCode :: MonadIO m => DynFlags -> m ()
checkBrokenTablesNextToCode :: DynFlags -> m ()
checkBrokenTablesNextToCode DynFlags
dflags
= do { Bool
broken <- DynFlags -> m Bool
forall (m :: * -> *). MonadIO m => DynFlags -> m Bool
Evidence bound by a type signature of the constraint type MonadIO m
checkBrokenTablesNextToCode' DynFlags
dflags
; Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
External instance of the constraint type forall (m :: * -> *). Monad m => Applicative m
External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m
Evidence bound by a type signature of the constraint type MonadIO m
when Bool
broken
(m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ do { Any
_ <- IO Any -> m Any
forall (m :: * -> *) a. MonadIO m => IO a -> m a
Evidence bound by a type signature of the constraint type MonadIO m
liftIO (IO Any -> m Any) -> IO Any -> m Any
forall a b. (a -> b) -> a -> b
$ GhcApiError -> IO Any
forall e a. Exception e => e -> IO a
External instance of the constraint type Exception GhcApiError
throwIO (GhcApiError -> IO Any) -> GhcApiError -> IO Any
forall a b. (a -> b) -> a -> b
$ DynFlags -> SDoc -> GhcApiError
mkApiErr DynFlags
dflags SDoc
invalidLdErr
; IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
Evidence bound by a type signature of the constraint type MonadIO m
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ FatalMessager
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
External instance of the constraint type MonadFail IO
fail FilePath
"unsupported linker"
}
}
where
invalidLdErr :: SDoc
invalidLdErr = FilePath -> SDoc
text FilePath
"Tables-next-to-code not supported on ARM" SDoc -> SDoc -> SDoc
<+>
FilePath -> SDoc
text FilePath
"when using binutils ld (please see:" SDoc -> SDoc -> SDoc
<+>
FilePath -> SDoc
text FilePath
"https://sourceware.org/bugzilla/show_bug.cgi?id=16177)"
checkBrokenTablesNextToCode' :: MonadIO m => DynFlags -> m Bool
checkBrokenTablesNextToCode' :: DynFlags -> m Bool
checkBrokenTablesNextToCode' DynFlags
dflags
| Bool -> Bool
not (Arch -> Bool
isARM Arch
arch) = Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m
Evidence bound by a type signature of the constraint type MonadIO m
return Bool
False
| Way
WayDyn Way -> Set Way -> Bool
forall a. Ord a => a -> Set a -> Bool
External instance of the constraint type Ord Way
`S.notMember` DynFlags -> Set Way
ways DynFlags
dflags = Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m
Evidence bound by a type signature of the constraint type MonadIO m
return Bool
False
| Bool -> Bool
not (DynFlags -> Bool
tablesNextToCode DynFlags
dflags) = Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m
Evidence bound by a type signature of the constraint type MonadIO m
return Bool
False
| Bool
otherwise = do
LinkerInfo
linkerInfo <- IO LinkerInfo -> m LinkerInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
Evidence bound by a type signature of the constraint type MonadIO m
liftIO (IO LinkerInfo -> m LinkerInfo) -> IO LinkerInfo -> m LinkerInfo
forall a b. (a -> b) -> a -> b
$ DynFlags -> IO LinkerInfo
getLinkerInfo DynFlags
dflags
case LinkerInfo
linkerInfo of
GnuLD [Option]
_ -> Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m
Evidence bound by a type signature of the constraint type MonadIO m
return Bool
True
LinkerInfo
_ -> Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m
Evidence bound by a type signature of the constraint type MonadIO m
return Bool
False
where platform :: Platform
platform = DynFlags -> Platform
targetPlatform DynFlags
dflags
arch :: Arch
arch = Platform -> Arch
platformArch Platform
platform
setSessionDynFlags :: GhcMonad m => DynFlags -> m [UnitId]
setSessionDynFlags :: DynFlags -> m [UnitId]
setSessionDynFlags DynFlags
dflags = do
DynFlags
dflags' <- DynFlags -> m DynFlags
forall (m :: * -> *). MonadIO m => DynFlags -> m DynFlags
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
checkNewDynFlags DynFlags
dflags
(DynFlags
dflags''', [UnitId]
preload) <- IO (DynFlags, [UnitId]) -> m (DynFlags, [UnitId])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO (DynFlags, [UnitId]) -> m (DynFlags, [UnitId]))
-> IO (DynFlags, [UnitId]) -> m (DynFlags, [UnitId])
forall a b. (a -> b) -> a -> b
$ DynFlags -> IO (DynFlags, [UnitId])
initPackages DynFlags
dflags'
Maybe Interp
interp <- if GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_ExternalInterpreter DynFlags
dflags
then do
let
prog :: FilePath
prog = DynFlags -> FilePath
pgm_i DynFlags
dflags FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
flavour
flavour :: FilePath
flavour
| Way
WayProf Way -> Set Way -> Bool
forall a. Ord a => a -> Set a -> Bool
External instance of the constraint type Ord Way
`S.member` DynFlags -> Set Way
ways DynFlags
dflags = FilePath
"-prof"
| Way
WayDyn Way -> Set Way -> Bool
forall a. Ord a => a -> Set a -> Bool
External instance of the constraint type Ord Way
`S.member` DynFlags -> Set Way
ways DynFlags
dflags = FilePath
"-dyn"
| Bool
otherwise = FilePath
""
msg :: SDoc
msg = FilePath -> SDoc
text FilePath
"Starting " SDoc -> SDoc -> SDoc
<> FilePath -> SDoc
text FilePath
prog
IO ()
tr <- if DynFlags -> Int
verbosity DynFlags
dflags Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
>= Int
3
then IO () -> m (IO ())
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (DynFlags -> SDoc -> IO ()
logInfo DynFlags
dflags (SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
defaultDumpStyle SDoc
msg)
else IO () -> m (IO ())
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative IO
pure ())
let
conf :: IServConfig
conf = IServConfig :: FilePath
-> [FilePath]
-> Bool
-> Bool
-> Maybe (CreateProcess -> IO ProcessHandle)
-> IO ()
-> IServConfig
IServConfig
{ iservConfProgram :: FilePath
iservConfProgram = FilePath
prog
, iservConfOpts :: [FilePath]
iservConfOpts = DynFlags -> (DynFlags -> [FilePath]) -> [FilePath]
forall a. DynFlags -> (DynFlags -> [a]) -> [a]
getOpts DynFlags
dflags DynFlags -> [FilePath]
opt_i
, iservConfProfiled :: Bool
iservConfProfiled = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_SccProfilingOn DynFlags
dflags
, iservConfDynamic :: Bool
iservConfDynamic = Way
WayDyn Way -> Set Way -> Bool
forall a. Ord a => a -> Set a -> Bool
External instance of the constraint type Ord Way
`S.member` DynFlags -> Set Way
ways DynFlags
dflags
, iservConfHook :: Maybe (CreateProcess -> IO ProcessHandle)
iservConfHook = Hooks -> Maybe (CreateProcess -> IO ProcessHandle)
createIservProcessHook (DynFlags -> Hooks
hooks DynFlags
dflags)
, iservConfTrace :: IO ()
iservConfTrace = IO ()
tr
}
MVar IServState
s <- IO (MVar IServState) -> m (MVar IServState)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO (MVar IServState) -> m (MVar IServState))
-> IO (MVar IServState) -> m (MVar IServState)
forall a b. (a -> b) -> a -> b
$ IServState -> IO (MVar IServState)
forall a. a -> IO (MVar a)
newMVar IServState
IServPending
Maybe Interp -> m (Maybe Interp)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (Interp -> Maybe Interp
forall a. a -> Maybe a
Just (IServConfig -> IServ -> Interp
ExternalInterp IServConfig
conf (MVar IServState -> IServ
IServ MVar IServState
s)))
else
#if defined(HAVE_INTERNAL_INTERPRETER)
Maybe Interp -> m (Maybe Interp)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (Interp -> Maybe Interp
forall a. a -> Maybe a
Just Interp
InternalInterp)
#else
return Nothing
#endif
(HscEnv -> HscEnv) -> m ()
forall (m :: * -> *). GhcMonad m => (HscEnv -> HscEnv) -> m ()
Evidence bound by a type signature of the constraint type GhcMonad m
modifySession ((HscEnv -> HscEnv) -> m ()) -> (HscEnv -> HscEnv) -> m ()
forall a b. (a -> b) -> a -> b
$ \HscEnv
h -> HscEnv
h{ hsc_dflags :: DynFlags
hsc_dflags = DynFlags
dflags'''
, hsc_IC :: InteractiveContext
hsc_IC = (HscEnv -> InteractiveContext
hsc_IC HscEnv
h){ ic_dflags :: DynFlags
ic_dflags = DynFlags
dflags''' }
, hsc_interp :: Maybe Interp
hsc_interp = HscEnv -> Maybe Interp
hsc_interp HscEnv
h Maybe Interp -> Maybe Interp -> Maybe Interp
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
External instance of the constraint type Alternative Maybe
<|> Maybe Interp
interp
}
m ()
forall (m :: * -> *). GhcMonad m => m ()
Evidence bound by a type signature of the constraint type GhcMonad m
invalidateModSummaryCache
[UnitId] -> m [UnitId]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return [UnitId]
preload
setProgramDynFlags :: GhcMonad m => DynFlags -> m [UnitId]
setProgramDynFlags :: DynFlags -> m [UnitId]
setProgramDynFlags DynFlags
dflags = Bool -> DynFlags -> m [UnitId]
forall (m :: * -> *). GhcMonad m => Bool -> DynFlags -> m [UnitId]
Evidence bound by a type signature of the constraint type GhcMonad m
setProgramDynFlags_ Bool
True DynFlags
dflags
setLogAction :: GhcMonad m => LogAction -> m ()
setLogAction :: LogAction -> m ()
setLogAction LogAction
action = do
DynFlags
dflags' <- m DynFlags
forall (m :: * -> *). GhcMonad m => m DynFlags
Evidence bound by a type signature of the constraint type GhcMonad m
getProgramDynFlags
m [UnitId] -> m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
External instance of the constraint type forall (m :: * -> *). GhcMonad m => Functor m
Evidence bound by a type signature of the constraint type GhcMonad m
void (m [UnitId] -> m ()) -> m [UnitId] -> m ()
forall a b. (a -> b) -> a -> b
$ Bool -> DynFlags -> m [UnitId]
forall (m :: * -> *). GhcMonad m => Bool -> DynFlags -> m [UnitId]
Evidence bound by a type signature of the constraint type GhcMonad m
setProgramDynFlags_ Bool
False (DynFlags -> m [UnitId]) -> DynFlags -> m [UnitId]
forall a b. (a -> b) -> a -> b
$
DynFlags
dflags' { log_action :: LogAction
log_action = LogAction
action }
setProgramDynFlags_ :: GhcMonad m => Bool -> DynFlags -> m [UnitId]
setProgramDynFlags_ :: Bool -> DynFlags -> m [UnitId]
setProgramDynFlags_ Bool
invalidate_needed DynFlags
dflags = do
DynFlags
dflags' <- DynFlags -> m DynFlags
forall (m :: * -> *). MonadIO m => DynFlags -> m DynFlags
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
checkNewDynFlags DynFlags
dflags
DynFlags
dflags_prev <- m DynFlags
forall (m :: * -> *). GhcMonad m => m DynFlags
Evidence bound by a type signature of the constraint type GhcMonad m
getProgramDynFlags
(DynFlags
dflags'', [UnitId]
preload) <-
if (DynFlags -> DynFlags -> Bool
packageFlagsChanged DynFlags
dflags_prev DynFlags
dflags')
then IO (DynFlags, [UnitId]) -> m (DynFlags, [UnitId])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO (DynFlags, [UnitId]) -> m (DynFlags, [UnitId]))
-> IO (DynFlags, [UnitId]) -> m (DynFlags, [UnitId])
forall a b. (a -> b) -> a -> b
$ DynFlags -> IO (DynFlags, [UnitId])
initPackages DynFlags
dflags'
else (DynFlags, [UnitId]) -> m (DynFlags, [UnitId])
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (DynFlags
dflags', [])
(HscEnv -> HscEnv) -> m ()
forall (m :: * -> *). GhcMonad m => (HscEnv -> HscEnv) -> m ()
Evidence bound by a type signature of the constraint type GhcMonad m
modifySession ((HscEnv -> HscEnv) -> m ()) -> (HscEnv -> HscEnv) -> m ()
forall a b. (a -> b) -> a -> b
$ \HscEnv
h -> HscEnv
h{ hsc_dflags :: DynFlags
hsc_dflags = DynFlags
dflags'' }
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
External instance of the constraint type forall (m :: * -> *). Monad m => Applicative m
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
when Bool
invalidate_needed (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ m ()
forall (m :: * -> *). GhcMonad m => m ()
Evidence bound by a type signature of the constraint type GhcMonad m
invalidateModSummaryCache
[UnitId] -> m [UnitId]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return [UnitId]
preload
invalidateModSummaryCache :: GhcMonad m => m ()
invalidateModSummaryCache :: m ()
invalidateModSummaryCache =
(HscEnv -> HscEnv) -> m ()
forall (m :: * -> *). GhcMonad m => (HscEnv -> HscEnv) -> m ()
Evidence bound by a type signature of the constraint type GhcMonad m
modifySession ((HscEnv -> HscEnv) -> m ()) -> (HscEnv -> HscEnv) -> m ()
forall a b. (a -> b) -> a -> b
$ \HscEnv
h -> HscEnv
h { hsc_mod_graph :: ModuleGraph
hsc_mod_graph = (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph
mapMG ModSummary -> ModSummary
inval (HscEnv -> ModuleGraph
hsc_mod_graph HscEnv
h) }
where
inval :: ModSummary -> ModSummary
inval ModSummary
ms = ModSummary
ms { ms_hs_date :: UTCTime
ms_hs_date = NominalDiffTime -> UTCTime -> UTCTime
addUTCTime (-NominalDiffTime
1) (ModSummary -> UTCTime
ms_hs_date ModSummary
ms) }
getProgramDynFlags :: GhcMonad m => m DynFlags
getProgramDynFlags :: m DynFlags
getProgramDynFlags = m DynFlags
forall (m :: * -> *). GhcMonad m => m DynFlags
Evidence bound by a type signature of the constraint type GhcMonad m
getSessionDynFlags
setInteractiveDynFlags :: GhcMonad m => DynFlags -> m ()
setInteractiveDynFlags :: DynFlags -> m ()
setInteractiveDynFlags DynFlags
dflags = do
DynFlags
dflags' <- DynFlags -> m DynFlags
forall (m :: * -> *). MonadIO m => DynFlags -> m DynFlags
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
checkNewDynFlags DynFlags
dflags
DynFlags
dflags'' <- DynFlags -> m DynFlags
forall (m :: * -> *). MonadIO m => DynFlags -> m DynFlags
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
checkNewInteractiveDynFlags DynFlags
dflags'
(HscEnv -> HscEnv) -> m ()
forall (m :: * -> *). GhcMonad m => (HscEnv -> HscEnv) -> m ()
Evidence bound by a type signature of the constraint type GhcMonad m
modifySession ((HscEnv -> HscEnv) -> m ()) -> (HscEnv -> HscEnv) -> m ()
forall a b. (a -> b) -> a -> b
$ \HscEnv
h -> HscEnv
h{ hsc_IC :: InteractiveContext
hsc_IC = (HscEnv -> InteractiveContext
hsc_IC HscEnv
h) { ic_dflags :: DynFlags
ic_dflags = DynFlags
dflags'' }}
getInteractiveDynFlags :: GhcMonad m => m DynFlags
getInteractiveDynFlags :: m DynFlags
getInteractiveDynFlags = (HscEnv -> m DynFlags) -> m DynFlags
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSession ((HscEnv -> m DynFlags) -> m DynFlags)
-> (HscEnv -> m DynFlags) -> m DynFlags
forall a b. (a -> b) -> a -> b
$ \HscEnv
h -> DynFlags -> m DynFlags
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (InteractiveContext -> DynFlags
ic_dflags (HscEnv -> InteractiveContext
hsc_IC HscEnv
h))
parseDynamicFlags :: MonadIO m =>
DynFlags -> [Located String]
-> m (DynFlags, [Located String], [Warn])
parseDynamicFlags :: DynFlags
-> [Located FilePath] -> m (DynFlags, [Located FilePath], [Warn])
parseDynamicFlags DynFlags
dflags [Located FilePath]
cmdline = do
(DynFlags
dflags1, [Located FilePath]
leftovers, [Warn]
warns) <- DynFlags
-> [Located FilePath] -> m (DynFlags, [Located FilePath], [Warn])
forall (m :: * -> *).
MonadIO m =>
DynFlags
-> [Located FilePath] -> m (DynFlags, [Located FilePath], [Warn])
Evidence bound by a type signature of the constraint type MonadIO m
parseDynamicFlagsCmdLine DynFlags
dflags [Located FilePath]
cmdline
DynFlags
dflags2 <- IO DynFlags -> m DynFlags
forall (m :: * -> *) a. MonadIO m => IO a -> m a
Evidence bound by a type signature of the constraint type MonadIO m
liftIO (IO DynFlags -> m DynFlags) -> IO DynFlags -> m DynFlags
forall a b. (a -> b) -> a -> b
$ DynFlags -> IO DynFlags
interpretPackageEnv DynFlags
dflags1
(DynFlags, [Located FilePath], [Warn])
-> m (DynFlags, [Located FilePath], [Warn])
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m
Evidence bound by a type signature of the constraint type MonadIO m
return (DynFlags
dflags2, [Located FilePath]
leftovers, [Warn]
warns)
checkNewDynFlags :: MonadIO m => DynFlags -> m DynFlags
checkNewDynFlags :: DynFlags -> m DynFlags
checkNewDynFlags DynFlags
dflags = do
let (DynFlags
dflags', [Located FilePath]
warnings) = DynFlags -> (DynFlags, [Located FilePath])
makeDynFlagsConsistent DynFlags
dflags
IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
Evidence bound by a type signature of the constraint type MonadIO m
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DynFlags -> [Warn] -> IO ()
handleFlagWarnings DynFlags
dflags ((Located FilePath -> Warn) -> [Located FilePath] -> [Warn]
forall a b. (a -> b) -> [a] -> [b]
map (WarnReason -> Located FilePath -> Warn
Warn WarnReason
NoReason) [Located FilePath]
warnings)
DynFlags -> m DynFlags
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m
Evidence bound by a type signature of the constraint type MonadIO m
return DynFlags
dflags'
checkNewInteractiveDynFlags :: MonadIO m => DynFlags -> m DynFlags
checkNewInteractiveDynFlags :: DynFlags -> m DynFlags
checkNewInteractiveDynFlags DynFlags
dflags0 = do
if Extension -> DynFlags -> Bool
xopt Extension
LangExt.StaticPointers DynFlags
dflags0
then do IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
Evidence bound by a type signature of the constraint type MonadIO m
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DynFlags -> Bag WarnMsg -> IO ()
printOrThrowWarnings DynFlags
dflags0 (Bag WarnMsg -> IO ()) -> Bag WarnMsg -> IO ()
forall a b. (a -> b) -> a -> b
$ [WarnMsg] -> Bag WarnMsg
forall a. [a] -> Bag a
listToBag
[DynFlags -> SrcSpan -> SDoc -> WarnMsg
mkPlainWarnMsg DynFlags
dflags0 SrcSpan
interactiveSrcSpan
(SDoc -> WarnMsg) -> SDoc -> WarnMsg
forall a b. (a -> b) -> a -> b
$ FilePath -> SDoc
text FilePath
"StaticPointers is not supported in GHCi interactive expressions."]
DynFlags -> m DynFlags
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m
Evidence bound by a type signature of the constraint type MonadIO m
return (DynFlags -> m DynFlags) -> DynFlags -> m DynFlags
forall a b. (a -> b) -> a -> b
$ DynFlags -> Extension -> DynFlags
xopt_unset DynFlags
dflags0 Extension
LangExt.StaticPointers
else DynFlags -> m DynFlags
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m
Evidence bound by a type signature of the constraint type MonadIO m
return DynFlags
dflags0
setTargets :: GhcMonad m => [Target] -> m ()
setTargets :: [Target] -> m ()
setTargets [Target]
targets = (HscEnv -> HscEnv) -> m ()
forall (m :: * -> *). GhcMonad m => (HscEnv -> HscEnv) -> m ()
Evidence bound by a type signature of the constraint type GhcMonad m
modifySession (\HscEnv
h -> HscEnv
h{ hsc_targets :: [Target]
hsc_targets = [Target]
targets })
getTargets :: GhcMonad m => m [Target]
getTargets :: m [Target]
getTargets = (HscEnv -> m [Target]) -> m [Target]
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSession ([Target] -> m [Target]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return ([Target] -> m [Target])
-> (HscEnv -> [Target]) -> HscEnv -> m [Target]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HscEnv -> [Target]
hsc_targets)
addTarget :: GhcMonad m => Target -> m ()
addTarget :: Target -> m ()
addTarget Target
target
= (HscEnv -> HscEnv) -> m ()
forall (m :: * -> *). GhcMonad m => (HscEnv -> HscEnv) -> m ()
Evidence bound by a type signature of the constraint type GhcMonad m
modifySession (\HscEnv
h -> HscEnv
h{ hsc_targets :: [Target]
hsc_targets = Target
target Target -> [Target] -> [Target]
forall a. a -> [a] -> [a]
: HscEnv -> [Target]
hsc_targets HscEnv
h })
removeTarget :: GhcMonad m => TargetId -> m ()
removeTarget :: TargetId -> m ()
removeTarget TargetId
target_id
= (HscEnv -> HscEnv) -> m ()
forall (m :: * -> *). GhcMonad m => (HscEnv -> HscEnv) -> m ()
Evidence bound by a type signature of the constraint type GhcMonad m
modifySession (\HscEnv
h -> HscEnv
h{ hsc_targets :: [Target]
hsc_targets = [Target] -> [Target]
filter (HscEnv -> [Target]
hsc_targets HscEnv
h) })
where
filter :: [Target] -> [Target]
filter [Target]
targets = [ Target
t | t :: Target
t@(Target TargetId
id Bool
_ Maybe (InputFileBuffer, UTCTime)
_) <- [Target]
targets, TargetId
id TargetId -> TargetId -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq TargetId
/= TargetId
target_id ]
guessTarget :: GhcMonad m => String -> Maybe Phase -> m Target
guessTarget :: FilePath -> Maybe Phase -> m Target
guessTarget FilePath
str (Just Phase
phase)
= Target -> m Target
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (TargetId -> Bool -> Maybe (InputFileBuffer, UTCTime) -> Target
Target (FilePath -> Maybe Phase -> TargetId
TargetFile FilePath
str (Phase -> Maybe Phase
forall a. a -> Maybe a
Just Phase
phase)) Bool
True Maybe (InputFileBuffer, UTCTime)
forall a. Maybe a
Nothing)
guessTarget FilePath
str Maybe Phase
Nothing
| FilePath -> Bool
isHaskellSrcFilename FilePath
file
= Target -> m Target
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (TargetId -> Target
target (FilePath -> Maybe Phase -> TargetId
TargetFile FilePath
file Maybe Phase
forall a. Maybe a
Nothing))
| Bool
otherwise
= do Bool
exists <- IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
doesFileExist FilePath
hs_file
if Bool
exists
then Target -> m Target
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (TargetId -> Target
target (FilePath -> Maybe Phase -> TargetId
TargetFile FilePath
hs_file Maybe Phase
forall a. Maybe a
Nothing))
else do
Bool
exists <- IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
doesFileExist FilePath
lhs_file
if Bool
exists
then Target -> m Target
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (TargetId -> Target
target (FilePath -> Maybe Phase -> TargetId
TargetFile FilePath
lhs_file Maybe Phase
forall a. Maybe a
Nothing))
else do
if FilePath -> Bool
looksLikeModuleName FilePath
file
then Target -> m Target
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (TargetId -> Target
target (ModuleName -> TargetId
TargetModule (FilePath -> ModuleName
mkModuleName FilePath
file)))
else do
DynFlags
dflags <- m DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
External instance of the constraint type forall (m :: * -> *). GhcMonad m => HasDynFlags m
Evidence bound by a type signature of the constraint type GhcMonad m
getDynFlags
IO Target -> m Target
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO Target -> m Target) -> IO Target -> m Target
forall a b. (a -> b) -> a -> b
$ GhcException -> IO Target
forall a. GhcException -> IO a
throwGhcExceptionIO
(FilePath -> GhcException
ProgramError (DynFlags -> SDoc -> FilePath
showSDoc DynFlags
dflags (SDoc -> FilePath) -> SDoc -> FilePath
forall a b. (a -> b) -> a -> b
$
FilePath -> SDoc
text FilePath
"target" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (FilePath -> SDoc
text FilePath
file) SDoc -> SDoc -> SDoc
<+>
FilePath -> SDoc
text FilePath
"is not a module name or a source file"))
where
(FilePath
file,Bool
obj_allowed)
| Char
'*':FilePath
rest <- FilePath
str = (FilePath
rest, Bool
False)
| Bool
otherwise = (FilePath
str, Bool
True)
hs_file :: FilePath
hs_file = FilePath
file FilePath -> FilePath -> FilePath
<.> FilePath
"hs"
lhs_file :: FilePath
lhs_file = FilePath
file FilePath -> FilePath -> FilePath
<.> FilePath
"lhs"
target :: TargetId -> Target
target TargetId
tid = TargetId -> Bool -> Maybe (InputFileBuffer, UTCTime) -> Target
Target TargetId
tid Bool
obj_allowed Maybe (InputFileBuffer, UTCTime)
forall a. Maybe a
Nothing
workingDirectoryChanged :: GhcMonad m => m ()
workingDirectoryChanged :: m ()
workingDirectoryChanged = (HscEnv -> m ()) -> m ()
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSession ((HscEnv -> m ()) -> m ()) -> (HscEnv -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ (IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO () -> m ()) -> (HscEnv -> IO ()) -> HscEnv -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HscEnv -> IO ()
flushFinderCaches)
class ParsedMod m where
modSummary :: m -> ModSummary
parsedSource :: m -> ParsedSource
class ParsedMod m => TypecheckedMod m where
renamedSource :: m -> Maybe RenamedSource
typecheckedSource :: m -> TypecheckedSource
moduleInfo :: m -> ModuleInfo
tm_internals :: m -> (TcGblEnv, ModDetails)
class TypecheckedMod m => DesugaredMod m where
coreModule :: m -> ModGuts
data ParsedModule =
ParsedModule { ParsedModule -> ModSummary
pm_mod_summary :: ModSummary
, ParsedModule -> ParsedSource
pm_parsed_source :: ParsedSource
, :: [FilePath]
, ParsedModule -> ApiAnns
pm_annotations :: ApiAnns }
instance ParsedMod ParsedModule where
modSummary :: ParsedModule -> ModSummary
modSummary ParsedModule
m = ParsedModule -> ModSummary
pm_mod_summary ParsedModule
m
parsedSource :: ParsedModule -> ParsedSource
parsedSource ParsedModule
m = ParsedModule -> ParsedSource
pm_parsed_source ParsedModule
m
data TypecheckedModule =
TypecheckedModule { TypecheckedModule -> ParsedModule
tm_parsed_module :: ParsedModule
, TypecheckedModule -> Maybe RenamedSource
tm_renamed_source :: Maybe RenamedSource
, TypecheckedModule -> TypecheckedSource
tm_typechecked_source :: TypecheckedSource
, TypecheckedModule -> ModuleInfo
tm_checked_module_info :: ModuleInfo
, TypecheckedModule -> (TcGblEnv, ModDetails)
tm_internals_ :: (TcGblEnv, ModDetails)
}
instance ParsedMod TypecheckedModule where
modSummary :: TypecheckedModule -> ModSummary
modSummary TypecheckedModule
m = ParsedModule -> ModSummary
forall m. ParsedMod m => m -> ModSummary
Instance of class: ParsedMod of the constraint type ParsedMod ParsedModule
modSummary (TypecheckedModule -> ParsedModule
tm_parsed_module TypecheckedModule
m)
parsedSource :: TypecheckedModule -> ParsedSource
parsedSource TypecheckedModule
m = ParsedModule -> ParsedSource
forall m. ParsedMod m => m -> ParsedSource
Instance of class: ParsedMod of the constraint type ParsedMod ParsedModule
parsedSource (TypecheckedModule -> ParsedModule
tm_parsed_module TypecheckedModule
m)
instance TypecheckedMod TypecheckedModule where
renamedSource :: TypecheckedModule -> Maybe RenamedSource
renamedSource TypecheckedModule
m = TypecheckedModule -> Maybe RenamedSource
tm_renamed_source TypecheckedModule
m
typecheckedSource :: TypecheckedModule -> TypecheckedSource
typecheckedSource TypecheckedModule
m = TypecheckedModule -> TypecheckedSource
tm_typechecked_source TypecheckedModule
m
moduleInfo :: TypecheckedModule -> ModuleInfo
moduleInfo TypecheckedModule
m = TypecheckedModule -> ModuleInfo
tm_checked_module_info TypecheckedModule
m
tm_internals :: TypecheckedModule -> (TcGblEnv, ModDetails)
tm_internals TypecheckedModule
m = TypecheckedModule -> (TcGblEnv, ModDetails)
tm_internals_ TypecheckedModule
m
data DesugaredModule =
DesugaredModule { DesugaredModule -> TypecheckedModule
dm_typechecked_module :: TypecheckedModule
, DesugaredModule -> ModGuts
dm_core_module :: ModGuts
}
instance ParsedMod DesugaredModule where
modSummary :: DesugaredModule -> ModSummary
modSummary DesugaredModule
m = TypecheckedModule -> ModSummary
forall m. ParsedMod m => m -> ModSummary
Instance of class: ParsedMod of the constraint type ParsedMod TypecheckedModule
modSummary (DesugaredModule -> TypecheckedModule
dm_typechecked_module DesugaredModule
m)
parsedSource :: DesugaredModule -> ParsedSource
parsedSource DesugaredModule
m = TypecheckedModule -> ParsedSource
forall m. ParsedMod m => m -> ParsedSource
Instance of class: ParsedMod of the constraint type ParsedMod TypecheckedModule
parsedSource (DesugaredModule -> TypecheckedModule
dm_typechecked_module DesugaredModule
m)
instance TypecheckedMod DesugaredModule where
renamedSource :: DesugaredModule -> Maybe RenamedSource
renamedSource DesugaredModule
m = TypecheckedModule -> Maybe RenamedSource
forall m. TypecheckedMod m => m -> Maybe RenamedSource
Instance of class: TypecheckedMod of the constraint type TypecheckedMod TypecheckedModule
renamedSource (DesugaredModule -> TypecheckedModule
dm_typechecked_module DesugaredModule
m)
typecheckedSource :: DesugaredModule -> TypecheckedSource
typecheckedSource DesugaredModule
m = TypecheckedModule -> TypecheckedSource
forall m. TypecheckedMod m => m -> TypecheckedSource
Instance of class: TypecheckedMod of the constraint type TypecheckedMod TypecheckedModule
typecheckedSource (DesugaredModule -> TypecheckedModule
dm_typechecked_module DesugaredModule
m)
moduleInfo :: DesugaredModule -> ModuleInfo
moduleInfo DesugaredModule
m = TypecheckedModule -> ModuleInfo
forall m. TypecheckedMod m => m -> ModuleInfo
Instance of class: TypecheckedMod of the constraint type TypecheckedMod TypecheckedModule
moduleInfo (DesugaredModule -> TypecheckedModule
dm_typechecked_module DesugaredModule
m)
tm_internals :: DesugaredModule -> (TcGblEnv, ModDetails)
tm_internals DesugaredModule
m = TypecheckedModule -> (TcGblEnv, ModDetails)
tm_internals_ (DesugaredModule -> TypecheckedModule
dm_typechecked_module DesugaredModule
m)
instance DesugaredMod DesugaredModule where
coreModule :: DesugaredModule -> ModGuts
coreModule DesugaredModule
m = DesugaredModule -> ModGuts
dm_core_module DesugaredModule
m
type ParsedSource = Located HsModule
type RenamedSource = (HsGroup GhcRn, [LImportDecl GhcRn], Maybe [(LIE GhcRn, Avails)],
Maybe LHsDocString)
type TypecheckedSource = LHsBinds GhcTc
getModSummary :: GhcMonad m => ModuleName -> m ModSummary
getModSummary :: ModuleName -> m ModSummary
getModSummary ModuleName
mod = do
ModuleGraph
mg <- (HscEnv -> ModuleGraph) -> m HscEnv -> m ModuleGraph
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftM HscEnv -> ModuleGraph
hsc_mod_graph m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
Evidence bound by a type signature of the constraint type GhcMonad m
getSession
let mods_by_name :: [ModSummary]
mods_by_name = [ ModSummary
ms | ModSummary
ms <- ModuleGraph -> [ModSummary]
mgModSummaries ModuleGraph
mg
, ModSummary -> ModuleName
ms_mod_name ModSummary
ms ModuleName -> ModuleName -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq ModuleName
== ModuleName
mod
, Bool -> Bool
not (ModSummary -> Bool
isBootSummary ModSummary
ms) ]
case [ModSummary]
mods_by_name of
[] -> do DynFlags
dflags <- m DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
External instance of the constraint type forall (m :: * -> *). GhcMonad m => HasDynFlags m
Evidence bound by a type signature of the constraint type GhcMonad m
getDynFlags
IO ModSummary -> m ModSummary
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO ModSummary -> m ModSummary) -> IO ModSummary -> m ModSummary
forall a b. (a -> b) -> a -> b
$ GhcApiError -> IO ModSummary
forall e a. Exception e => e -> IO a
External instance of the constraint type Exception GhcApiError
throwIO (GhcApiError -> IO ModSummary) -> GhcApiError -> IO ModSummary
forall a b. (a -> b) -> a -> b
$ DynFlags -> SDoc -> GhcApiError
mkApiErr DynFlags
dflags (FilePath -> SDoc
text FilePath
"Module not part of module graph")
[ModSummary
ms] -> ModSummary -> m ModSummary
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return ModSummary
ms
[ModSummary]
multiple -> do DynFlags
dflags <- m DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
External instance of the constraint type forall (m :: * -> *). GhcMonad m => HasDynFlags m
Evidence bound by a type signature of the constraint type GhcMonad m
getDynFlags
IO ModSummary -> m ModSummary
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO ModSummary -> m ModSummary) -> IO ModSummary -> m ModSummary
forall a b. (a -> b) -> a -> b
$ GhcApiError -> IO ModSummary
forall e a. Exception e => e -> IO a
External instance of the constraint type Exception GhcApiError
throwIO (GhcApiError -> IO ModSummary) -> GhcApiError -> IO ModSummary
forall a b. (a -> b) -> a -> b
$ DynFlags -> SDoc -> GhcApiError
mkApiErr DynFlags
dflags (FilePath -> SDoc
text FilePath
"getModSummary is ambiguous: " SDoc -> SDoc -> SDoc
<+> [ModSummary] -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall a. Outputable a => Outputable [a]
External instance of the constraint type Outputable ModSummary
ppr [ModSummary]
multiple)
parseModule :: GhcMonad m => ModSummary -> m ParsedModule
parseModule :: ModSummary -> m ParsedModule
parseModule ModSummary
ms = do
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
Evidence bound by a type signature of the constraint type GhcMonad m
getSession
let hsc_env_tmp :: HscEnv
hsc_env_tmp = HscEnv
hsc_env { hsc_dflags :: DynFlags
hsc_dflags = ModSummary -> DynFlags
ms_hspp_opts ModSummary
ms }
HsParsedModule
hpm <- IO HsParsedModule -> m HsParsedModule
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO HsParsedModule -> m HsParsedModule)
-> IO HsParsedModule -> m HsParsedModule
forall a b. (a -> b) -> a -> b
$ HscEnv -> ModSummary -> IO HsParsedModule
hscParse HscEnv
hsc_env_tmp ModSummary
ms
ParsedModule -> m ParsedModule
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (ModSummary -> ParsedSource -> [FilePath] -> ApiAnns -> ParsedModule
ParsedModule ModSummary
ms (HsParsedModule -> ParsedSource
hpm_module HsParsedModule
hpm) (HsParsedModule -> [FilePath]
hpm_src_files HsParsedModule
hpm)
(HsParsedModule -> ApiAnns
hpm_annotations HsParsedModule
hpm))
typecheckModule :: GhcMonad m => ParsedModule -> m TypecheckedModule
typecheckModule :: ParsedModule -> m TypecheckedModule
typecheckModule ParsedModule
pmod = do
let ms :: ModSummary
ms = ParsedModule -> ModSummary
forall m. ParsedMod m => m -> ModSummary
Instance of class: ParsedMod of the constraint type ParsedMod ParsedModule
modSummary ParsedModule
pmod
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
Evidence bound by a type signature of the constraint type GhcMonad m
getSession
let hsc_env_tmp :: HscEnv
hsc_env_tmp = HscEnv
hsc_env { hsc_dflags :: DynFlags
hsc_dflags = ModSummary -> DynFlags
ms_hspp_opts ModSummary
ms }
(TcGblEnv
tc_gbl_env, Maybe RenamedSource
rn_info)
<- IO (TcGblEnv, Maybe RenamedSource)
-> m (TcGblEnv, Maybe RenamedSource)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO (TcGblEnv, Maybe RenamedSource)
-> m (TcGblEnv, Maybe RenamedSource))
-> IO (TcGblEnv, Maybe RenamedSource)
-> m (TcGblEnv, Maybe RenamedSource)
forall a b. (a -> b) -> a -> b
$ HscEnv
-> ModSummary
-> HsParsedModule
-> IO (TcGblEnv, Maybe RenamedSource)
hscTypecheckRename HscEnv
hsc_env_tmp ModSummary
ms (HsParsedModule -> IO (TcGblEnv, Maybe RenamedSource))
-> HsParsedModule -> IO (TcGblEnv, Maybe RenamedSource)
forall a b. (a -> b) -> a -> b
$
HsParsedModule :: ParsedSource -> [FilePath] -> ApiAnns -> HsParsedModule
HsParsedModule { hpm_module :: ParsedSource
hpm_module = ParsedModule -> ParsedSource
forall m. ParsedMod m => m -> ParsedSource
Instance of class: ParsedMod of the constraint type ParsedMod ParsedModule
parsedSource ParsedModule
pmod,
hpm_src_files :: [FilePath]
hpm_src_files = ParsedModule -> [FilePath]
pm_extra_src_files ParsedModule
pmod,
hpm_annotations :: ApiAnns
hpm_annotations = ParsedModule -> ApiAnns
pm_annotations ParsedModule
pmod }
ModDetails
details <- IO ModDetails -> m ModDetails
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO ModDetails -> m ModDetails) -> IO ModDetails -> m ModDetails
forall a b. (a -> b) -> a -> b
$ HscEnv -> TcGblEnv -> IO ModDetails
makeSimpleDetails HscEnv
hsc_env_tmp TcGblEnv
tc_gbl_env
SafeHaskellMode
safe <- IO SafeHaskellMode -> m SafeHaskellMode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO SafeHaskellMode -> m SafeHaskellMode)
-> IO SafeHaskellMode -> m SafeHaskellMode
forall a b. (a -> b) -> a -> b
$ DynFlags -> TcGblEnv -> IO SafeHaskellMode
finalSafeMode (ModSummary -> DynFlags
ms_hspp_opts ModSummary
ms) TcGblEnv
tc_gbl_env
TypecheckedModule -> m TypecheckedModule
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (TypecheckedModule -> m TypecheckedModule)
-> TypecheckedModule -> m TypecheckedModule
forall a b. (a -> b) -> a -> b
$
TypecheckedModule :: ParsedModule
-> Maybe RenamedSource
-> TypecheckedSource
-> ModuleInfo
-> (TcGblEnv, ModDetails)
-> TypecheckedModule
TypecheckedModule {
tm_internals_ :: (TcGblEnv, ModDetails)
tm_internals_ = (TcGblEnv
tc_gbl_env, ModDetails
details),
tm_parsed_module :: ParsedModule
tm_parsed_module = ParsedModule
pmod,
tm_renamed_source :: Maybe RenamedSource
tm_renamed_source = Maybe RenamedSource
rn_info,
tm_typechecked_source :: TypecheckedSource
tm_typechecked_source = TcGblEnv -> TypecheckedSource
tcg_binds TcGblEnv
tc_gbl_env,
tm_checked_module_info :: ModuleInfo
tm_checked_module_info =
ModuleInfo :: TypeEnv
-> [AvailInfo]
-> Maybe GlobalRdrEnv
-> [ClsInst]
-> Maybe ModIface
-> SafeHaskellMode
-> ModBreaks
-> ModuleInfo
ModuleInfo {
minf_type_env :: TypeEnv
minf_type_env = ModDetails -> TypeEnv
md_types ModDetails
details,
minf_exports :: [AvailInfo]
minf_exports = ModDetails -> [AvailInfo]
md_exports ModDetails
details,
minf_rdr_env :: Maybe GlobalRdrEnv
minf_rdr_env = GlobalRdrEnv -> Maybe GlobalRdrEnv
forall a. a -> Maybe a
Just (TcGblEnv -> GlobalRdrEnv
tcg_rdr_env TcGblEnv
tc_gbl_env),
minf_instances :: [ClsInst]
minf_instances = SafeHaskellMode -> [ClsInst] -> [ClsInst]
fixSafeInstances SafeHaskellMode
safe ([ClsInst] -> [ClsInst]) -> [ClsInst] -> [ClsInst]
forall a b. (a -> b) -> a -> b
$ ModDetails -> [ClsInst]
md_insts ModDetails
details,
minf_iface :: Maybe ModIface
minf_iface = Maybe ModIface
forall a. Maybe a
Nothing,
minf_safe :: SafeHaskellMode
minf_safe = SafeHaskellMode
safe,
minf_modBreaks :: ModBreaks
minf_modBreaks = ModBreaks
emptyModBreaks
}}
desugarModule :: GhcMonad m => TypecheckedModule -> m DesugaredModule
desugarModule :: TypecheckedModule -> m DesugaredModule
desugarModule TypecheckedModule
tcm = do
let ms :: ModSummary
ms = TypecheckedModule -> ModSummary
forall m. ParsedMod m => m -> ModSummary
Instance of class: ParsedMod of the constraint type ParsedMod TypecheckedModule
modSummary TypecheckedModule
tcm
let (TcGblEnv
tcg, ModDetails
_) = TypecheckedModule -> (TcGblEnv, ModDetails)
forall m. TypecheckedMod m => m -> (TcGblEnv, ModDetails)
Instance of class: TypecheckedMod of the constraint type TypecheckedMod TypecheckedModule
tm_internals TypecheckedModule
tcm
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
Evidence bound by a type signature of the constraint type GhcMonad m
getSession
let hsc_env_tmp :: HscEnv
hsc_env_tmp = HscEnv
hsc_env { hsc_dflags :: DynFlags
hsc_dflags = ModSummary -> DynFlags
ms_hspp_opts ModSummary
ms }
ModGuts
guts <- IO ModGuts -> m ModGuts
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO ModGuts -> m ModGuts) -> IO ModGuts -> m ModGuts
forall a b. (a -> b) -> a -> b
$ HscEnv -> ModSummary -> TcGblEnv -> IO ModGuts
hscDesugar HscEnv
hsc_env_tmp ModSummary
ms TcGblEnv
tcg
DesugaredModule -> m DesugaredModule
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (DesugaredModule -> m DesugaredModule)
-> DesugaredModule -> m DesugaredModule
forall a b. (a -> b) -> a -> b
$
DesugaredModule :: TypecheckedModule -> ModGuts -> DesugaredModule
DesugaredModule {
dm_typechecked_module :: TypecheckedModule
dm_typechecked_module = TypecheckedModule
tcm,
dm_core_module :: ModGuts
dm_core_module = ModGuts
guts
}
loadModule :: (TypecheckedMod mod, GhcMonad m) => mod -> m mod
loadModule :: mod -> m mod
loadModule mod
tcm = do
let ms :: ModSummary
ms = mod -> ModSummary
forall m. ParsedMod m => m -> ModSummary
Evidence bound by a superclass of: TypecheckedMod of the constraint type forall m. TypecheckedMod m => ParsedMod m
Evidence bound by a type signature of the constraint type TypecheckedMod mod
modSummary mod
tcm
let mod :: ModuleName
mod = ModSummary -> ModuleName
ms_mod_name ModSummary
ms
let loc :: ModLocation
loc = ModSummary -> ModLocation
ms_location ModSummary
ms
let (TcGblEnv
tcg, ModDetails
_details) = mod -> (TcGblEnv, ModDetails)
forall m. TypecheckedMod m => m -> (TcGblEnv, ModDetails)
Evidence bound by a type signature of the constraint type TypecheckedMod mod
tm_internals mod
tcm
Maybe Linkable
mb_linkable <- case ModSummary -> Maybe UTCTime
ms_obj_date ModSummary
ms of
Just UTCTime
t | UTCTime
t UTCTime -> UTCTime -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord UTCTime
> ModSummary -> UTCTime
ms_hs_date ModSummary
ms -> do
Linkable
l <- IO Linkable -> m Linkable
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO Linkable -> m Linkable) -> IO Linkable -> m Linkable
forall a b. (a -> b) -> a -> b
$ Module -> FilePath -> UTCTime -> IO Linkable
findObjectLinkable (ModSummary -> Module
ms_mod ModSummary
ms)
(ModLocation -> FilePath
ml_obj_file ModLocation
loc) UTCTime
t
Maybe Linkable -> m (Maybe Linkable)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (Linkable -> Maybe Linkable
forall a. a -> Maybe a
Just Linkable
l)
Maybe UTCTime
_otherwise -> Maybe Linkable -> m (Maybe Linkable)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return Maybe Linkable
forall a. Maybe a
Nothing
let source_modified :: SourceModified
source_modified | Maybe Linkable -> Bool
forall a. Maybe a -> Bool
isNothing Maybe Linkable
mb_linkable = SourceModified
SourceModified
| Bool
otherwise = SourceModified
SourceUnmodified
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
Evidence bound by a type signature of the constraint type GhcMonad m
getSession
HomeModInfo
mod_info <- IO HomeModInfo -> m HomeModInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO HomeModInfo -> m HomeModInfo)
-> IO HomeModInfo -> m HomeModInfo
forall a b. (a -> b) -> a -> b
$ Maybe TcGblEnv
-> Maybe Messager
-> HscEnv
-> ModSummary
-> Int
-> Int
-> Maybe ModIface
-> Maybe Linkable
-> SourceModified
-> IO HomeModInfo
compileOne' (TcGblEnv -> Maybe TcGblEnv
forall a. a -> Maybe a
Just TcGblEnv
tcg) Maybe Messager
forall a. Maybe a
Nothing
HscEnv
hsc_env ModSummary
ms Int
1 Int
1 Maybe ModIface
forall a. Maybe a
Nothing Maybe Linkable
mb_linkable
SourceModified
source_modified
(HscEnv -> HscEnv) -> m ()
forall (m :: * -> *). GhcMonad m => (HscEnv -> HscEnv) -> m ()
Evidence bound by a type signature of the constraint type GhcMonad m
modifySession ((HscEnv -> HscEnv) -> m ()) -> (HscEnv -> HscEnv) -> m ()
forall a b. (a -> b) -> a -> b
$ \HscEnv
e -> HscEnv
e{ hsc_HPT :: HomePackageTable
hsc_HPT = HomePackageTable -> ModuleName -> HomeModInfo -> HomePackageTable
addToHpt (HscEnv -> HomePackageTable
hsc_HPT HscEnv
e) ModuleName
mod HomeModInfo
mod_info }
mod -> m mod
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return mod
tcm
data CoreModule
= CoreModule {
CoreModule -> Module
cm_module :: !Module,
CoreModule -> TypeEnv
cm_types :: !TypeEnv,
CoreModule -> CoreProgram
cm_binds :: CoreProgram,
CoreModule -> SafeHaskellMode
cm_safe :: SafeHaskellMode
}
instance Outputable CoreModule where
ppr :: CoreModule -> SDoc
ppr (CoreModule {cm_module :: CoreModule -> Module
cm_module = Module
mn, cm_types :: CoreModule -> TypeEnv
cm_types = TypeEnv
te, cm_binds :: CoreModule -> CoreProgram
cm_binds = CoreProgram
cb,
cm_safe :: CoreModule -> SafeHaskellMode
cm_safe = SafeHaskellMode
sf})
= FilePath -> SDoc
text FilePath
"%module" SDoc -> SDoc -> SDoc
<+> Module -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Module
ppr Module
mn SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
parens (SafeHaskellMode -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable SafeHaskellMode
ppr SafeHaskellMode
sf) SDoc -> SDoc -> SDoc
<+> TypeEnv -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall a. Outputable a => Outputable (UniqFM a)
External instance of the constraint type Outputable TyThing
ppr TypeEnv
te
SDoc -> SDoc -> SDoc
$$ [SDoc] -> SDoc
vcat ((CoreBind -> SDoc) -> CoreProgram -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map CoreBind -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall b. OutputableBndr b => Outputable (Bind b)
External instance of the constraint type OutputableBndr Var
ppr CoreProgram
cb)
compileToCoreModule :: GhcMonad m => FilePath -> m CoreModule
compileToCoreModule :: FilePath -> m CoreModule
compileToCoreModule = Bool -> FilePath -> m CoreModule
forall (m :: * -> *).
GhcMonad m =>
Bool -> FilePath -> m CoreModule
Evidence bound by a type signature of the constraint type GhcMonad m
compileCore Bool
False
compileToCoreSimplified :: GhcMonad m => FilePath -> m CoreModule
compileToCoreSimplified :: FilePath -> m CoreModule
compileToCoreSimplified = Bool -> FilePath -> m CoreModule
forall (m :: * -> *).
GhcMonad m =>
Bool -> FilePath -> m CoreModule
Evidence bound by a type signature of the constraint type GhcMonad m
compileCore Bool
True
compileCore :: GhcMonad m => Bool -> FilePath -> m CoreModule
compileCore :: Bool -> FilePath -> m CoreModule
compileCore Bool
simplify FilePath
fn = do
Target
target <- FilePath -> Maybe Phase -> m Target
forall (m :: * -> *).
GhcMonad m =>
FilePath -> Maybe Phase -> m Target
Evidence bound by a type signature of the constraint type GhcMonad m
guessTarget FilePath
fn Maybe Phase
forall a. Maybe a
Nothing
Target -> m ()
forall (m :: * -> *). GhcMonad m => Target -> m ()
Evidence bound by a type signature of the constraint type GhcMonad m
addTarget Target
target
SuccessFlag
_ <- LoadHowMuch -> m SuccessFlag
forall (m :: * -> *). GhcMonad m => LoadHowMuch -> m SuccessFlag
Evidence bound by a type signature of the constraint type GhcMonad m
load LoadHowMuch
LoadAllTargets
ModuleGraph
modGraph <- [ModuleName] -> Bool -> m ModuleGraph
forall (m :: * -> *).
GhcMonad m =>
[ModuleName] -> Bool -> m ModuleGraph
Evidence bound by a type signature of the constraint type GhcMonad m
depanal [] Bool
True
case (ModSummary -> Bool) -> [ModSummary] -> Maybe ModSummary
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
External instance of the constraint type Foldable []
find ((FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
== FilePath
fn) (FilePath -> Bool)
-> (ModSummary -> FilePath) -> ModSummary -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModSummary -> FilePath
msHsFilePath) (ModuleGraph -> [ModSummary]
mgModSummaries ModuleGraph
modGraph) of
Just ModSummary
modSummary -> do
(TcGblEnv
tcg, ModGuts
mod_guts) <-
do TypecheckedModule
tm <- ParsedModule -> m TypecheckedModule
forall (m :: * -> *).
GhcMonad m =>
ParsedModule -> m TypecheckedModule
Evidence bound by a type signature of the constraint type GhcMonad m
typecheckModule (ParsedModule -> m TypecheckedModule)
-> m ParsedModule -> m TypecheckedModule
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
=<< ModSummary -> m ParsedModule
forall (m :: * -> *). GhcMonad m => ModSummary -> m ParsedModule
Evidence bound by a type signature of the constraint type GhcMonad m
parseModule ModSummary
modSummary
let tcg :: TcGblEnv
tcg = (TcGblEnv, ModDetails) -> TcGblEnv
forall a b. (a, b) -> a
fst (TypecheckedModule -> (TcGblEnv, ModDetails)
forall m. TypecheckedMod m => m -> (TcGblEnv, ModDetails)
Instance of class: TypecheckedMod of the constraint type TypecheckedMod TypecheckedModule
tm_internals TypecheckedModule
tm)
(,) TcGblEnv
tcg (ModGuts -> (TcGblEnv, ModGuts))
-> (DesugaredModule -> ModGuts)
-> DesugaredModule
-> (TcGblEnv, ModGuts)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DesugaredModule -> ModGuts
forall m. DesugaredMod m => m -> ModGuts
Instance of class: DesugaredMod of the constraint type DesugaredMod DesugaredModule
coreModule (DesugaredModule -> (TcGblEnv, ModGuts))
-> m DesugaredModule -> m (TcGblEnv, ModGuts)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (m :: * -> *). GhcMonad m => Functor m
Evidence bound by a type signature of the constraint type GhcMonad m
<$> TypecheckedModule -> m DesugaredModule
forall (m :: * -> *).
GhcMonad m =>
TypecheckedModule -> m DesugaredModule
Evidence bound by a type signature of the constraint type GhcMonad m
desugarModule TypecheckedModule
tm
(Either (CgGuts, ModDetails) ModGuts -> CoreModule)
-> m (Either (CgGuts, ModDetails) ModGuts) -> m CoreModule
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftM (SafeHaskellMode
-> Either (CgGuts, ModDetails) ModGuts -> CoreModule
gutsToCoreModule (ModGuts -> SafeHaskellMode
mg_safe_haskell ModGuts
mod_guts)) (m (Either (CgGuts, ModDetails) ModGuts) -> m CoreModule)
-> m (Either (CgGuts, ModDetails) ModGuts) -> m CoreModule
forall a b. (a -> b) -> a -> b
$
if Bool
simplify
then do
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
Evidence bound by a type signature of the constraint type GhcMonad m
getSession
ModGuts
simpl_guts <- IO ModGuts -> m ModGuts
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO ModGuts -> m ModGuts) -> IO ModGuts -> m ModGuts
forall a b. (a -> b) -> a -> b
$ do
[FilePath]
plugins <- IORef [FilePath] -> IO [FilePath]
forall a. IORef a -> IO a
readIORef (TcGblEnv -> IORef [FilePath]
tcg_th_coreplugins TcGblEnv
tcg)
HscEnv -> [FilePath] -> ModGuts -> IO ModGuts
hscSimplify HscEnv
hsc_env [FilePath]
plugins ModGuts
mod_guts
(CgGuts, ModDetails)
tidy_guts <- IO (CgGuts, ModDetails) -> m (CgGuts, ModDetails)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO (CgGuts, ModDetails) -> m (CgGuts, ModDetails))
-> IO (CgGuts, ModDetails) -> m (CgGuts, ModDetails)
forall a b. (a -> b) -> a -> b
$ HscEnv -> ModGuts -> IO (CgGuts, ModDetails)
tidyProgram HscEnv
hsc_env ModGuts
simpl_guts
Either (CgGuts, ModDetails) ModGuts
-> m (Either (CgGuts, ModDetails) ModGuts)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (Either (CgGuts, ModDetails) ModGuts
-> m (Either (CgGuts, ModDetails) ModGuts))
-> Either (CgGuts, ModDetails) ModGuts
-> m (Either (CgGuts, ModDetails) ModGuts)
forall a b. (a -> b) -> a -> b
$ (CgGuts, ModDetails) -> Either (CgGuts, ModDetails) ModGuts
forall a b. a -> Either a b
Left (CgGuts, ModDetails)
tidy_guts
else
Either (CgGuts, ModDetails) ModGuts
-> m (Either (CgGuts, ModDetails) ModGuts)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (Either (CgGuts, ModDetails) ModGuts
-> m (Either (CgGuts, ModDetails) ModGuts))
-> Either (CgGuts, ModDetails) ModGuts
-> m (Either (CgGuts, ModDetails) ModGuts)
forall a b. (a -> b) -> a -> b
$ ModGuts -> Either (CgGuts, ModDetails) ModGuts
forall a b. b -> Either a b
Right ModGuts
mod_guts
Maybe ModSummary
Nothing -> FilePath -> m CoreModule
forall a. FilePath -> a
panic "compileToCoreModule: target FilePath not found in\
module dependency graph"
where
gutsToCoreModule :: SafeHaskellMode
-> Either (CgGuts, ModDetails) ModGuts
-> CoreModule
gutsToCoreModule :: SafeHaskellMode
-> Either (CgGuts, ModDetails) ModGuts -> CoreModule
gutsToCoreModule SafeHaskellMode
safe_mode (Left (CgGuts
cg, ModDetails
md)) = CoreModule :: Module -> TypeEnv -> CoreProgram -> SafeHaskellMode -> CoreModule
CoreModule {
cm_module :: Module
cm_module = CgGuts -> Module
cg_module CgGuts
cg,
cm_types :: TypeEnv
cm_types = ModDetails -> TypeEnv
md_types ModDetails
md,
cm_binds :: CoreProgram
cm_binds = CgGuts -> CoreProgram
cg_binds CgGuts
cg,
cm_safe :: SafeHaskellMode
cm_safe = SafeHaskellMode
safe_mode
}
gutsToCoreModule SafeHaskellMode
safe_mode (Right ModGuts
mg) = CoreModule :: Module -> TypeEnv -> CoreProgram -> SafeHaskellMode -> CoreModule
CoreModule {
cm_module :: Module
cm_module = ModGuts -> Module
mg_module ModGuts
mg,
cm_types :: TypeEnv
cm_types = [Var] -> [TyCon] -> [FamInst] -> TypeEnv
typeEnvFromEntities (CoreProgram -> [Var]
forall b. [Bind b] -> [b]
bindersOfBinds (ModGuts -> CoreProgram
mg_binds ModGuts
mg))
(ModGuts -> [TyCon]
mg_tcs ModGuts
mg)
(ModGuts -> [FamInst]
mg_fam_insts ModGuts
mg),
cm_binds :: CoreProgram
cm_binds = ModGuts -> CoreProgram
mg_binds ModGuts
mg,
cm_safe :: SafeHaskellMode
cm_safe = SafeHaskellMode
safe_mode
}
getModuleGraph :: GhcMonad m => m ModuleGraph
getModuleGraph :: m ModuleGraph
getModuleGraph = (HscEnv -> ModuleGraph) -> m HscEnv -> m ModuleGraph
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftM HscEnv -> ModuleGraph
hsc_mod_graph m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
Evidence bound by a type signature of the constraint type GhcMonad m
getSession
isLoaded :: GhcMonad m => ModuleName -> m Bool
isLoaded :: ModuleName -> m Bool
isLoaded ModuleName
m = (HscEnv -> m Bool) -> m Bool
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSession ((HscEnv -> m Bool) -> m Bool) -> (HscEnv -> m Bool) -> m Bool
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env ->
Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (Bool -> m Bool) -> Bool -> m Bool
forall a b. (a -> b) -> a -> b
$! Maybe HomeModInfo -> Bool
forall a. Maybe a -> Bool
isJust (HomePackageTable -> ModuleName -> Maybe HomeModInfo
lookupHpt (HscEnv -> HomePackageTable
hsc_HPT HscEnv
hsc_env) ModuleName
m)
getBindings :: GhcMonad m => m [TyThing]
getBindings :: m [TyThing]
getBindings = (HscEnv -> m [TyThing]) -> m [TyThing]
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSession ((HscEnv -> m [TyThing]) -> m [TyThing])
-> (HscEnv -> m [TyThing]) -> m [TyThing]
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env ->
[TyThing] -> m [TyThing]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return ([TyThing] -> m [TyThing]) -> [TyThing] -> m [TyThing]
forall a b. (a -> b) -> a -> b
$ InteractiveContext -> [TyThing]
icInScopeTTs (InteractiveContext -> [TyThing])
-> InteractiveContext -> [TyThing]
forall a b. (a -> b) -> a -> b
$ HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env
getInsts :: GhcMonad m => m ([ClsInst], [FamInst])
getInsts :: m ([ClsInst], [FamInst])
getInsts = (HscEnv -> m ([ClsInst], [FamInst])) -> m ([ClsInst], [FamInst])
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSession ((HscEnv -> m ([ClsInst], [FamInst])) -> m ([ClsInst], [FamInst]))
-> (HscEnv -> m ([ClsInst], [FamInst])) -> m ([ClsInst], [FamInst])
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env ->
([ClsInst], [FamInst]) -> m ([ClsInst], [FamInst])
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (([ClsInst], [FamInst]) -> m ([ClsInst], [FamInst]))
-> ([ClsInst], [FamInst]) -> m ([ClsInst], [FamInst])
forall a b. (a -> b) -> a -> b
$ InteractiveContext -> ([ClsInst], [FamInst])
ic_instances (HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env)
getPrintUnqual :: GhcMonad m => m PrintUnqualified
getPrintUnqual :: m PrintUnqualified
getPrintUnqual = (HscEnv -> m PrintUnqualified) -> m PrintUnqualified
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSession ((HscEnv -> m PrintUnqualified) -> m PrintUnqualified)
-> (HscEnv -> m PrintUnqualified) -> m PrintUnqualified
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env ->
PrintUnqualified -> m PrintUnqualified
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (DynFlags -> InteractiveContext -> PrintUnqualified
icPrintUnqual (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env) (HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env))
data ModuleInfo = ModuleInfo {
ModuleInfo -> TypeEnv
minf_type_env :: TypeEnv,
ModuleInfo -> [AvailInfo]
minf_exports :: [AvailInfo],
ModuleInfo -> Maybe GlobalRdrEnv
minf_rdr_env :: Maybe GlobalRdrEnv,
ModuleInfo -> [ClsInst]
minf_instances :: [ClsInst],
ModuleInfo -> Maybe ModIface
minf_iface :: Maybe ModIface,
ModuleInfo -> SafeHaskellMode
minf_safe :: SafeHaskellMode,
ModuleInfo -> ModBreaks
minf_modBreaks :: ModBreaks
}
getModuleInfo :: GhcMonad m => Module -> m (Maybe ModuleInfo)
getModuleInfo :: Module -> m (Maybe ModuleInfo)
getModuleInfo Module
mdl = (HscEnv -> m (Maybe ModuleInfo)) -> m (Maybe ModuleInfo)
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSession ((HscEnv -> m (Maybe ModuleInfo)) -> m (Maybe ModuleInfo))
-> (HscEnv -> m (Maybe ModuleInfo)) -> m (Maybe ModuleInfo)
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> do
let mg :: ModuleGraph
mg = HscEnv -> ModuleGraph
hsc_mod_graph HscEnv
hsc_env
if ModuleGraph -> Module -> Bool
mgElemModule ModuleGraph
mg Module
mdl
then IO (Maybe ModuleInfo) -> m (Maybe ModuleInfo)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO (Maybe ModuleInfo) -> m (Maybe ModuleInfo))
-> IO (Maybe ModuleInfo) -> m (Maybe ModuleInfo)
forall a b. (a -> b) -> a -> b
$ HscEnv -> Module -> IO (Maybe ModuleInfo)
getHomeModuleInfo HscEnv
hsc_env Module
mdl
else do
IO (Maybe ModuleInfo) -> m (Maybe ModuleInfo)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO (Maybe ModuleInfo) -> m (Maybe ModuleInfo))
-> IO (Maybe ModuleInfo) -> m (Maybe ModuleInfo)
forall a b. (a -> b) -> a -> b
$ HscEnv -> Module -> IO (Maybe ModuleInfo)
getPackageModuleInfo HscEnv
hsc_env Module
mdl
getPackageModuleInfo :: HscEnv -> Module -> IO (Maybe ModuleInfo)
getPackageModuleInfo :: HscEnv -> Module -> IO (Maybe ModuleInfo)
getPackageModuleInfo HscEnv
hsc_env Module
mdl
= do ExternalPackageState
eps <- HscEnv -> IO ExternalPackageState
hscEPS HscEnv
hsc_env
ModIface
iface <- HscEnv -> Module -> IO ModIface
hscGetModuleInterface HscEnv
hsc_env Module
mdl
let
avails :: [AvailInfo]
avails = ModIface -> [AvailInfo]
forall (phase :: ModIfacePhase). ModIface_ phase -> [AvailInfo]
mi_exports ModIface
iface
pte :: TypeEnv
pte = ExternalPackageState -> TypeEnv
eps_PTE ExternalPackageState
eps
tys :: [TyThing]
tys = [ TyThing
ty | Name
name <- (AvailInfo -> [Name]) -> [AvailInfo] -> [Name]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
External instance of the constraint type Foldable []
concatMap AvailInfo -> [Name]
availNames [AvailInfo]
avails,
Just TyThing
ty <- [TypeEnv -> Name -> Maybe TyThing
lookupTypeEnv TypeEnv
pte Name
name] ]
Maybe ModuleInfo -> IO (Maybe ModuleInfo)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return (ModuleInfo -> Maybe ModuleInfo
forall a. a -> Maybe a
Just (ModuleInfo :: TypeEnv
-> [AvailInfo]
-> Maybe GlobalRdrEnv
-> [ClsInst]
-> Maybe ModIface
-> SafeHaskellMode
-> ModBreaks
-> ModuleInfo
ModuleInfo {
minf_type_env :: TypeEnv
minf_type_env = [TyThing] -> TypeEnv
mkTypeEnv [TyThing]
tys,
minf_exports :: [AvailInfo]
minf_exports = [AvailInfo]
avails,
minf_rdr_env :: Maybe GlobalRdrEnv
minf_rdr_env = GlobalRdrEnv -> Maybe GlobalRdrEnv
forall a. a -> Maybe a
Just (GlobalRdrEnv -> Maybe GlobalRdrEnv)
-> GlobalRdrEnv -> Maybe GlobalRdrEnv
forall a b. (a -> b) -> a -> b
$! ModuleName -> [AvailInfo] -> GlobalRdrEnv
availsToGlobalRdrEnv (Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
mdl) [AvailInfo]
avails,
minf_instances :: [ClsInst]
minf_instances = FilePath -> [ClsInst]
forall a. HasCallStack => FilePath -> a
error FilePath
"getModuleInfo: instances for package module unimplemented",
minf_iface :: Maybe ModIface
minf_iface = ModIface -> Maybe ModIface
forall a. a -> Maybe a
Just ModIface
iface,
minf_safe :: SafeHaskellMode
minf_safe = IfaceTrustInfo -> SafeHaskellMode
getSafeMode (IfaceTrustInfo -> SafeHaskellMode)
-> IfaceTrustInfo -> SafeHaskellMode
forall a b. (a -> b) -> a -> b
$ ModIface -> IfaceTrustInfo
forall (phase :: ModIfacePhase). ModIface_ phase -> IfaceTrustInfo
mi_trust ModIface
iface,
minf_modBreaks :: ModBreaks
minf_modBreaks = ModBreaks
emptyModBreaks
}))
getHomeModuleInfo :: HscEnv -> Module -> IO (Maybe ModuleInfo)
getHomeModuleInfo :: HscEnv -> Module -> IO (Maybe ModuleInfo)
getHomeModuleInfo HscEnv
hsc_env Module
mdl =
case HomePackageTable -> ModuleName -> Maybe HomeModInfo
lookupHpt (HscEnv -> HomePackageTable
hsc_HPT HscEnv
hsc_env) (Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
mdl) of
Maybe HomeModInfo
Nothing -> Maybe ModuleInfo -> IO (Maybe ModuleInfo)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return Maybe ModuleInfo
forall a. Maybe a
Nothing
Just HomeModInfo
hmi -> do
let details :: ModDetails
details = HomeModInfo -> ModDetails
hm_details HomeModInfo
hmi
iface :: ModIface
iface = HomeModInfo -> ModIface
hm_iface HomeModInfo
hmi
Maybe ModuleInfo -> IO (Maybe ModuleInfo)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return (ModuleInfo -> Maybe ModuleInfo
forall a. a -> Maybe a
Just (ModuleInfo :: TypeEnv
-> [AvailInfo]
-> Maybe GlobalRdrEnv
-> [ClsInst]
-> Maybe ModIface
-> SafeHaskellMode
-> ModBreaks
-> ModuleInfo
ModuleInfo {
minf_type_env :: TypeEnv
minf_type_env = ModDetails -> TypeEnv
md_types ModDetails
details,
minf_exports :: [AvailInfo]
minf_exports = ModDetails -> [AvailInfo]
md_exports ModDetails
details,
minf_rdr_env :: Maybe GlobalRdrEnv
minf_rdr_env = ModIface -> Maybe GlobalRdrEnv
forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe GlobalRdrEnv
mi_globals (ModIface -> Maybe GlobalRdrEnv) -> ModIface -> Maybe GlobalRdrEnv
forall a b. (a -> b) -> a -> b
$! HomeModInfo -> ModIface
hm_iface HomeModInfo
hmi,
minf_instances :: [ClsInst]
minf_instances = ModDetails -> [ClsInst]
md_insts ModDetails
details,
minf_iface :: Maybe ModIface
minf_iface = ModIface -> Maybe ModIface
forall a. a -> Maybe a
Just ModIface
iface,
minf_safe :: SafeHaskellMode
minf_safe = IfaceTrustInfo -> SafeHaskellMode
getSafeMode (IfaceTrustInfo -> SafeHaskellMode)
-> IfaceTrustInfo -> SafeHaskellMode
forall a b. (a -> b) -> a -> b
$ ModIface -> IfaceTrustInfo
forall (phase :: ModIfacePhase). ModIface_ phase -> IfaceTrustInfo
mi_trust ModIface
iface
,minf_modBreaks :: ModBreaks
minf_modBreaks = HomeModInfo -> ModBreaks
getModBreaks HomeModInfo
hmi
}))
modInfoTyThings :: ModuleInfo -> [TyThing]
modInfoTyThings :: ModuleInfo -> [TyThing]
modInfoTyThings ModuleInfo
minf = TypeEnv -> [TyThing]
typeEnvElts (ModuleInfo -> TypeEnv
minf_type_env ModuleInfo
minf)
modInfoTopLevelScope :: ModuleInfo -> Maybe [Name]
modInfoTopLevelScope :: ModuleInfo -> Maybe [Name]
modInfoTopLevelScope ModuleInfo
minf
= (GlobalRdrEnv -> [Name]) -> Maybe GlobalRdrEnv -> Maybe [Name]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Maybe
fmap ((GlobalRdrElt -> Name) -> [GlobalRdrElt] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map GlobalRdrElt -> Name
gre_name ([GlobalRdrElt] -> [Name])
-> (GlobalRdrEnv -> [GlobalRdrElt]) -> GlobalRdrEnv -> [Name]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GlobalRdrEnv -> [GlobalRdrElt]
globalRdrEnvElts) (ModuleInfo -> Maybe GlobalRdrEnv
minf_rdr_env ModuleInfo
minf)
modInfoExports :: ModuleInfo -> [Name]
modInfoExports :: ModuleInfo -> [Name]
modInfoExports ModuleInfo
minf = (AvailInfo -> [Name]) -> [AvailInfo] -> [Name]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
External instance of the constraint type Foldable []
concatMap AvailInfo -> [Name]
availNames ([AvailInfo] -> [Name]) -> [AvailInfo] -> [Name]
forall a b. (a -> b) -> a -> b
$! ModuleInfo -> [AvailInfo]
minf_exports ModuleInfo
minf
modInfoExportsWithSelectors :: ModuleInfo -> [Name]
modInfoExportsWithSelectors :: ModuleInfo -> [Name]
modInfoExportsWithSelectors ModuleInfo
minf = (AvailInfo -> [Name]) -> [AvailInfo] -> [Name]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
External instance of the constraint type Foldable []
concatMap AvailInfo -> [Name]
availNamesWithSelectors ([AvailInfo] -> [Name]) -> [AvailInfo] -> [Name]
forall a b. (a -> b) -> a -> b
$! ModuleInfo -> [AvailInfo]
minf_exports ModuleInfo
minf
modInfoInstances :: ModuleInfo -> [ClsInst]
modInfoInstances :: ModuleInfo -> [ClsInst]
modInfoInstances = ModuleInfo -> [ClsInst]
minf_instances
modInfoIsExportedName :: ModuleInfo -> Name -> Bool
modInfoIsExportedName :: ModuleInfo -> Name -> Bool
modInfoIsExportedName ModuleInfo
minf Name
name = Name -> NameSet -> Bool
elemNameSet Name
name ([AvailInfo] -> NameSet
availsToNameSet (ModuleInfo -> [AvailInfo]
minf_exports ModuleInfo
minf))
mkPrintUnqualifiedForModule :: GhcMonad m =>
ModuleInfo
-> m (Maybe PrintUnqualified)
mkPrintUnqualifiedForModule :: ModuleInfo -> m (Maybe PrintUnqualified)
mkPrintUnqualifiedForModule ModuleInfo
minf = (HscEnv -> m (Maybe PrintUnqualified))
-> m (Maybe PrintUnqualified)
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSession ((HscEnv -> m (Maybe PrintUnqualified))
-> m (Maybe PrintUnqualified))
-> (HscEnv -> m (Maybe PrintUnqualified))
-> m (Maybe PrintUnqualified)
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> do
Maybe PrintUnqualified -> m (Maybe PrintUnqualified)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return ((GlobalRdrEnv -> PrintUnqualified)
-> Maybe GlobalRdrEnv -> Maybe PrintUnqualified
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Maybe
fmap (DynFlags -> GlobalRdrEnv -> PrintUnqualified
mkPrintUnqualified (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)) (ModuleInfo -> Maybe GlobalRdrEnv
minf_rdr_env ModuleInfo
minf))
modInfoLookupName :: GhcMonad m =>
ModuleInfo -> Name
-> m (Maybe TyThing)
modInfoLookupName :: ModuleInfo -> Name -> m (Maybe TyThing)
modInfoLookupName ModuleInfo
minf Name
name = (HscEnv -> m (Maybe TyThing)) -> m (Maybe TyThing)
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSession ((HscEnv -> m (Maybe TyThing)) -> m (Maybe TyThing))
-> (HscEnv -> m (Maybe TyThing)) -> m (Maybe TyThing)
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> do
case TypeEnv -> Name -> Maybe TyThing
lookupTypeEnv (ModuleInfo -> TypeEnv
minf_type_env ModuleInfo
minf) Name
name of
Just TyThing
tyThing -> Maybe TyThing -> m (Maybe TyThing)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (TyThing -> Maybe TyThing
forall a. a -> Maybe a
Just TyThing
tyThing)
Maybe TyThing
Nothing -> do
ExternalPackageState
eps <- IO ExternalPackageState -> m ExternalPackageState
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO ExternalPackageState -> m ExternalPackageState)
-> IO ExternalPackageState -> m ExternalPackageState
forall a b. (a -> b) -> a -> b
$ IORef ExternalPackageState -> IO ExternalPackageState
forall a. IORef a -> IO a
readIORef (HscEnv -> IORef ExternalPackageState
hsc_EPS HscEnv
hsc_env)
Maybe TyThing -> m (Maybe TyThing)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (Maybe TyThing -> m (Maybe TyThing))
-> Maybe TyThing -> m (Maybe TyThing)
forall a b. (a -> b) -> a -> b
$! DynFlags -> HomePackageTable -> TypeEnv -> Name -> Maybe TyThing
lookupType (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)
(HscEnv -> HomePackageTable
hsc_HPT HscEnv
hsc_env) (ExternalPackageState -> TypeEnv
eps_PTE ExternalPackageState
eps) Name
name
modInfoIface :: ModuleInfo -> Maybe ModIface
modInfoIface :: ModuleInfo -> Maybe ModIface
modInfoIface = ModuleInfo -> Maybe ModIface
minf_iface
modInfoRdrEnv :: ModuleInfo -> Maybe GlobalRdrEnv
modInfoRdrEnv :: ModuleInfo -> Maybe GlobalRdrEnv
modInfoRdrEnv = ModuleInfo -> Maybe GlobalRdrEnv
minf_rdr_env
modInfoSafe :: ModuleInfo -> SafeHaskellMode
modInfoSafe :: ModuleInfo -> SafeHaskellMode
modInfoSafe = ModuleInfo -> SafeHaskellMode
minf_safe
modInfoModBreaks :: ModuleInfo -> ModBreaks
modInfoModBreaks :: ModuleInfo -> ModBreaks
modInfoModBreaks = ModuleInfo -> ModBreaks
minf_modBreaks
isDictonaryId :: Id -> Bool
isDictonaryId :: Var -> Bool
isDictonaryId Var
id
= case Type -> ([Var], ThetaType, Type)
tcSplitSigmaTy (Var -> Type
idType Var
id) of {
([Var]
_tvs, ThetaType
_theta, Type
tau) -> Type -> Bool
isDictTy Type
tau }
lookupGlobalName :: GhcMonad m => Name -> m (Maybe TyThing)
lookupGlobalName :: Name -> m (Maybe TyThing)
lookupGlobalName Name
name = (HscEnv -> m (Maybe TyThing)) -> m (Maybe TyThing)
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSession ((HscEnv -> m (Maybe TyThing)) -> m (Maybe TyThing))
-> (HscEnv -> m (Maybe TyThing)) -> m (Maybe TyThing)
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> do
IO (Maybe TyThing) -> m (Maybe TyThing)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO (Maybe TyThing) -> m (Maybe TyThing))
-> IO (Maybe TyThing) -> m (Maybe TyThing)
forall a b. (a -> b) -> a -> b
$ HscEnv -> Name -> IO (Maybe TyThing)
lookupTypeHscEnv HscEnv
hsc_env Name
name
findGlobalAnns :: (GhcMonad m, Typeable a) => ([Word8] -> a) -> AnnTarget Name -> m [a]
findGlobalAnns :: ([Word8] -> a) -> AnnTarget Name -> m [a]
findGlobalAnns [Word8] -> a
deserialize AnnTarget Name
target = (HscEnv -> m [a]) -> m [a]
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSession ((HscEnv -> m [a]) -> m [a]) -> (HscEnv -> m [a]) -> m [a]
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> do
AnnEnv
ann_env <- IO AnnEnv -> m AnnEnv
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO AnnEnv -> m AnnEnv) -> IO AnnEnv -> m AnnEnv
forall a b. (a -> b) -> a -> b
$ HscEnv -> Maybe ModGuts -> IO AnnEnv
prepareAnnotations HscEnv
hsc_env Maybe ModGuts
forall a. Maybe a
Nothing
[a] -> m [a]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (([Word8] -> a) -> AnnEnv -> AnnTarget Name -> [a]
forall a.
Typeable a =>
([Word8] -> a) -> AnnEnv -> AnnTarget Name -> [a]
Evidence bound by a type signature of the constraint type Typeable a
findAnns [Word8] -> a
deserialize AnnEnv
ann_env AnnTarget Name
target)
getGRE :: GhcMonad m => m GlobalRdrEnv
getGRE :: m GlobalRdrEnv
getGRE = (HscEnv -> m GlobalRdrEnv) -> m GlobalRdrEnv
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSession ((HscEnv -> m GlobalRdrEnv) -> m GlobalRdrEnv)
-> (HscEnv -> m GlobalRdrEnv) -> m GlobalRdrEnv
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env-> GlobalRdrEnv -> m GlobalRdrEnv
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (GlobalRdrEnv -> m GlobalRdrEnv) -> GlobalRdrEnv -> m GlobalRdrEnv
forall a b. (a -> b) -> a -> b
$ InteractiveContext -> GlobalRdrEnv
ic_rn_gbl_env (HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env)
getNameToInstancesIndex :: GhcMonad m
=> [Module]
-> Maybe [Module]
-> m (Messages, Maybe (NameEnv ([ClsInst], [FamInst])))
getNameToInstancesIndex :: [Module]
-> Maybe [Module]
-> m (Messages, Maybe (NameEnv ([ClsInst], [FamInst])))
getNameToInstancesIndex [Module]
visible_mods Maybe [Module]
mods_to_load = do
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
Evidence bound by a type signature of the constraint type GhcMonad m
getSession
IO (Messages, Maybe (NameEnv ([ClsInst], [FamInst])))
-> m (Messages, Maybe (NameEnv ([ClsInst], [FamInst])))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO (Messages, Maybe (NameEnv ([ClsInst], [FamInst])))
-> m (Messages, Maybe (NameEnv ([ClsInst], [FamInst]))))
-> IO (Messages, Maybe (NameEnv ([ClsInst], [FamInst])))
-> m (Messages, Maybe (NameEnv ([ClsInst], [FamInst])))
forall a b. (a -> b) -> a -> b
$ HscEnv
-> TcRn (NameEnv ([ClsInst], [FamInst]))
-> IO (Messages, Maybe (NameEnv ([ClsInst], [FamInst])))
forall a. HscEnv -> TcRn a -> IO (Messages, Maybe a)
runTcInteractive HscEnv
hsc_env (TcRn (NameEnv ([ClsInst], [FamInst]))
-> IO (Messages, Maybe (NameEnv ([ClsInst], [FamInst]))))
-> TcRn (NameEnv ([ClsInst], [FamInst]))
-> IO (Messages, Maybe (NameEnv ([ClsInst], [FamInst])))
forall a b. (a -> b) -> a -> b
$
do { case Maybe [Module]
mods_to_load of
Maybe [Module]
Nothing -> HscEnv -> InteractiveContext -> IOEnv (Env TcGblEnv TcLclEnv) ()
loadUnqualIfaces HscEnv
hsc_env (HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env)
Just [Module]
mods ->
let doc :: SDoc
doc = FilePath -> SDoc
text FilePath
"Need interface for reporting instances in scope"
in IfG () -> IOEnv (Env TcGblEnv TcLclEnv) ()
forall a. IfG a -> TcRn a
initIfaceTcRn (IfG () -> IOEnv (Env TcGblEnv TcLclEnv) ())
-> IfG () -> IOEnv (Env TcGblEnv TcLclEnv) ()
forall a b. (a -> b) -> a -> b
$ (Module -> IOEnv (Env IfGblEnv ()) ModIface) -> [Module] -> IfG ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
External instance of the constraint type forall m. Monad (IOEnv m)
External instance of the constraint type Foldable []
mapM_ (SDoc -> Module -> IOEnv (Env IfGblEnv ()) ModIface
forall lcl. SDoc -> Module -> IfM lcl ModIface
loadSysInterface SDoc
doc) [Module]
mods
; InstEnvs {InstEnv
ie_global :: InstEnvs -> InstEnv
ie_global :: InstEnv
ie_global, InstEnv
ie_local :: InstEnvs -> InstEnv
ie_local :: InstEnv
ie_local} <- TcM InstEnvs
tcGetInstEnvs
; let visible_mods' :: ModuleSet
visible_mods' = [Module] -> ModuleSet
mkModuleSet [Module]
visible_mods
; (FamInstEnv
pkg_fie, FamInstEnv
home_fie) <- TcM (FamInstEnv, FamInstEnv)
tcGetFamInstEnvs
; let cls_index :: Map Name (Seq ClsInst)
cls_index = (Seq ClsInst -> Seq ClsInst -> Seq ClsInst)
-> [(Name, Seq ClsInst)] -> Map Name (Seq ClsInst)
forall k a. Ord k => (a -> a -> a) -> [(k, a)] -> Map k a
External instance of the constraint type Ord Name
Map.fromListWith Seq ClsInst -> Seq ClsInst -> Seq ClsInst
forall a. Monoid a => a -> a -> a
External instance of the constraint type forall a. Monoid (Seq a)
mappend
[ (Name
n, ClsInst -> Seq ClsInst
forall a. a -> Seq a
Seq.singleton ClsInst
ispec)
| ClsInst
ispec <- InstEnv -> [ClsInst]
instEnvElts InstEnv
ie_local [ClsInst] -> [ClsInst] -> [ClsInst]
forall a. [a] -> [a] -> [a]
++ InstEnv -> [ClsInst]
instEnvElts InstEnv
ie_global
, ModuleSet -> ClsInst -> Bool
instIsVisible ModuleSet
visible_mods' ClsInst
ispec
, Name
n <- NameSet -> [Name]
nameSetElemsStable (NameSet -> [Name]) -> NameSet -> [Name]
forall a b. (a -> b) -> a -> b
$ ClsInst -> NameSet
orphNamesOfClsInst ClsInst
ispec
]
; let fam_index :: Map Name (Seq FamInst)
fam_index = (Seq FamInst -> Seq FamInst -> Seq FamInst)
-> [(Name, Seq FamInst)] -> Map Name (Seq FamInst)
forall k a. Ord k => (a -> a -> a) -> [(k, a)] -> Map k a
External instance of the constraint type Ord Name
Map.fromListWith Seq FamInst -> Seq FamInst -> Seq FamInst
forall a. Monoid a => a -> a -> a
External instance of the constraint type forall a. Monoid (Seq a)
mappend
[ (Name
n, FamInst -> Seq FamInst
forall a. a -> Seq a
Seq.singleton FamInst
fispec)
| FamInst
fispec <- FamInstEnv -> [FamInst]
famInstEnvElts FamInstEnv
home_fie [FamInst] -> [FamInst] -> [FamInst]
forall a. [a] -> [a] -> [a]
++ FamInstEnv -> [FamInst]
famInstEnvElts FamInstEnv
pkg_fie
, Name
n <- NameSet -> [Name]
nameSetElemsStable (NameSet -> [Name]) -> NameSet -> [Name]
forall a b. (a -> b) -> a -> b
$ FamInst -> NameSet
orphNamesOfFamInst FamInst
fispec
]
; NameEnv ([ClsInst], [FamInst])
-> TcRn (NameEnv ([ClsInst], [FamInst]))
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (NameEnv ([ClsInst], [FamInst])
-> TcRn (NameEnv ([ClsInst], [FamInst])))
-> NameEnv ([ClsInst], [FamInst])
-> TcRn (NameEnv ([ClsInst], [FamInst]))
forall a b. (a -> b) -> a -> b
$ [(Name, ([ClsInst], [FamInst]))] -> NameEnv ([ClsInst], [FamInst])
forall a. [(Name, a)] -> NameEnv a
mkNameEnv ([(Name, ([ClsInst], [FamInst]))]
-> NameEnv ([ClsInst], [FamInst]))
-> [(Name, ([ClsInst], [FamInst]))]
-> NameEnv ([ClsInst], [FamInst])
forall a b. (a -> b) -> a -> b
$
[ (Name
nm, (Seq ClsInst -> [ClsInst]
forall (t :: * -> *) a. Foldable t => t a -> [a]
External instance of the constraint type Foldable Seq
toList Seq ClsInst
clss, Seq FamInst -> [FamInst]
forall (t :: * -> *) a. Foldable t => t a -> [a]
External instance of the constraint type Foldable Seq
toList Seq FamInst
fams))
| (Name
nm, (Seq ClsInst
clss, Seq FamInst
fams)) <- Map Name (Seq ClsInst, Seq FamInst)
-> [(Name, (Seq ClsInst, Seq FamInst))]
forall k a. Map k a -> [(k, a)]
Map.toList (Map Name (Seq ClsInst, Seq FamInst)
-> [(Name, (Seq ClsInst, Seq FamInst))])
-> Map Name (Seq ClsInst, Seq FamInst)
-> [(Name, (Seq ClsInst, Seq FamInst))]
forall a b. (a -> b) -> a -> b
$ ((Seq ClsInst, Seq FamInst)
-> (Seq ClsInst, Seq FamInst) -> (Seq ClsInst, Seq FamInst))
-> Map Name (Seq ClsInst, Seq FamInst)
-> Map Name (Seq ClsInst, Seq FamInst)
-> Map Name (Seq ClsInst, Seq FamInst)
forall k a. Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
External instance of the constraint type Ord Name
Map.unionWith (Seq ClsInst, Seq FamInst)
-> (Seq ClsInst, Seq FamInst) -> (Seq ClsInst, Seq FamInst)
forall a. Monoid a => a -> a -> a
External instance of the constraint type forall a b. (Monoid a, Monoid b) => Monoid (a, b)
External instance of the constraint type forall a. Monoid (Seq a)
External instance of the constraint type forall a. Monoid (Seq a)
mappend
((Seq ClsInst -> (Seq ClsInst, Seq FamInst))
-> Map Name (Seq ClsInst) -> Map Name (Seq ClsInst, Seq FamInst)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall k. Functor (Map k)
fmap (,Seq FamInst
forall a. Seq a
Seq.empty) Map Name (Seq ClsInst)
cls_index)
((Seq FamInst -> (Seq ClsInst, Seq FamInst))
-> Map Name (Seq FamInst) -> Map Name (Seq ClsInst, Seq FamInst)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall k. Functor (Map k)
fmap (Seq ClsInst
forall a. Seq a
Seq.empty,) Map Name (Seq FamInst)
fam_index)
] }
dataConType :: DataCon -> Type
dataConType :: DataCon -> Type
dataConType DataCon
dc = Var -> Type
idType (DataCon -> Var
dataConWrapId DataCon
dc)
pprParenSymName :: NamedThing a => a -> SDoc
pprParenSymName :: a -> SDoc
pprParenSymName a
a = OccName -> SDoc -> SDoc
parenSymOcc (a -> OccName
forall a. NamedThing a => a -> OccName
Evidence bound by a type signature of the constraint type NamedThing a
getOccName a
a) (Name -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Name
ppr (a -> Name
forall a. NamedThing a => a -> Name
Evidence bound by a type signature of the constraint type NamedThing a
getName a
a))
getModuleSourceAndFlags :: GhcMonad m => Module -> m (String, StringBuffer, DynFlags)
getModuleSourceAndFlags :: Module -> m (FilePath, InputFileBuffer, DynFlags)
getModuleSourceAndFlags Module
mod = do
ModSummary
m <- ModuleName -> m ModSummary
forall (m :: * -> *). GhcMonad m => ModuleName -> m ModSummary
Evidence bound by a type signature of the constraint type GhcMonad m
getModSummary (Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
mod)
case ModLocation -> Maybe FilePath
ml_hs_file (ModLocation -> Maybe FilePath) -> ModLocation -> Maybe FilePath
forall a b. (a -> b) -> a -> b
$ ModSummary -> ModLocation
ms_location ModSummary
m of
Maybe FilePath
Nothing -> do DynFlags
dflags <- m DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
External instance of the constraint type forall (m :: * -> *). GhcMonad m => HasDynFlags m
Evidence bound by a type signature of the constraint type GhcMonad m
getDynFlags
IO (FilePath, InputFileBuffer, DynFlags)
-> m (FilePath, InputFileBuffer, DynFlags)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO (FilePath, InputFileBuffer, DynFlags)
-> m (FilePath, InputFileBuffer, DynFlags))
-> IO (FilePath, InputFileBuffer, DynFlags)
-> m (FilePath, InputFileBuffer, DynFlags)
forall a b. (a -> b) -> a -> b
$ GhcApiError -> IO (FilePath, InputFileBuffer, DynFlags)
forall e a. Exception e => e -> IO a
External instance of the constraint type Exception GhcApiError
throwIO (GhcApiError -> IO (FilePath, InputFileBuffer, DynFlags))
-> GhcApiError -> IO (FilePath, InputFileBuffer, DynFlags)
forall a b. (a -> b) -> a -> b
$ DynFlags -> SDoc -> GhcApiError
mkApiErr DynFlags
dflags (FilePath -> SDoc
text FilePath
"No source available for module " SDoc -> SDoc -> SDoc
<+> Module -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Module
ppr Module
mod)
Just FilePath
sourceFile -> do
InputFileBuffer
source <- IO InputFileBuffer -> m InputFileBuffer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO InputFileBuffer -> m InputFileBuffer)
-> IO InputFileBuffer -> m InputFileBuffer
forall a b. (a -> b) -> a -> b
$ FilePath -> IO InputFileBuffer
hGetStringBuffer FilePath
sourceFile
(FilePath, InputFileBuffer, DynFlags)
-> m (FilePath, InputFileBuffer, DynFlags)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (FilePath
sourceFile, InputFileBuffer
source, ModSummary -> DynFlags
ms_hspp_opts ModSummary
m)
getTokenStream :: GhcMonad m => Module -> m [Located Token]
getTokenStream :: Module -> m [Located Token]
getTokenStream Module
mod = do
(FilePath
sourceFile, InputFileBuffer
source, DynFlags
flags) <- Module -> m (FilePath, InputFileBuffer, DynFlags)
forall (m :: * -> *).
GhcMonad m =>
Module -> m (FilePath, InputFileBuffer, DynFlags)
Evidence bound by a type signature of the constraint type GhcMonad m
getModuleSourceAndFlags Module
mod
let startLoc :: RealSrcLoc
startLoc = FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc (FilePath -> FastString
mkFastString FilePath
sourceFile) Int
1 Int
1
case InputFileBuffer
-> RealSrcLoc -> DynFlags -> ParseResult [Located Token]
lexTokenStream InputFileBuffer
source RealSrcLoc
startLoc DynFlags
flags of
POk PState
_ [Located Token]
ts -> [Located Token] -> m [Located Token]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return [Located Token]
ts
PFailed PState
pst ->
do DynFlags
dflags <- m DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
External instance of the constraint type forall (m :: * -> *). GhcMonad m => HasDynFlags m
Evidence bound by a type signature of the constraint type GhcMonad m
getDynFlags
Bag WarnMsg -> m [Located Token]
forall (io :: * -> *) a. MonadIO io => Bag WarnMsg -> io a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
throwErrors (PState -> DynFlags -> Bag WarnMsg
getErrorMessages PState
pst DynFlags
dflags)
getRichTokenStream :: GhcMonad m => Module -> m [(Located Token, String)]
getRichTokenStream :: Module -> m [(Located Token, FilePath)]
getRichTokenStream Module
mod = do
(FilePath
sourceFile, InputFileBuffer
source, DynFlags
flags) <- Module -> m (FilePath, InputFileBuffer, DynFlags)
forall (m :: * -> *).
GhcMonad m =>
Module -> m (FilePath, InputFileBuffer, DynFlags)
Evidence bound by a type signature of the constraint type GhcMonad m
getModuleSourceAndFlags Module
mod
let startLoc :: RealSrcLoc
startLoc = FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc (FilePath -> FastString
mkFastString FilePath
sourceFile) Int
1 Int
1
case InputFileBuffer
-> RealSrcLoc -> DynFlags -> ParseResult [Located Token]
lexTokenStream InputFileBuffer
source RealSrcLoc
startLoc DynFlags
flags of
POk PState
_ [Located Token]
ts -> [(Located Token, FilePath)] -> m [(Located Token, FilePath)]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return ([(Located Token, FilePath)] -> m [(Located Token, FilePath)])
-> [(Located Token, FilePath)] -> m [(Located Token, FilePath)]
forall a b. (a -> b) -> a -> b
$ RealSrcLoc
-> InputFileBuffer
-> [Located Token]
-> [(Located Token, FilePath)]
addSourceToTokens RealSrcLoc
startLoc InputFileBuffer
source [Located Token]
ts
PFailed PState
pst ->
do DynFlags
dflags <- m DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
External instance of the constraint type forall (m :: * -> *). GhcMonad m => HasDynFlags m
Evidence bound by a type signature of the constraint type GhcMonad m
getDynFlags
Bag WarnMsg -> m [(Located Token, FilePath)]
forall (io :: * -> *) a. MonadIO io => Bag WarnMsg -> io a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
throwErrors (PState -> DynFlags -> Bag WarnMsg
getErrorMessages PState
pst DynFlags
dflags)
addSourceToTokens :: RealSrcLoc -> StringBuffer -> [Located Token]
-> [(Located Token, String)]
addSourceToTokens :: RealSrcLoc
-> InputFileBuffer
-> [Located Token]
-> [(Located Token, FilePath)]
addSourceToTokens RealSrcLoc
_ InputFileBuffer
_ [] = []
addSourceToTokens RealSrcLoc
loc InputFileBuffer
buf (t :: Located Token
t@(L SrcSpan
span Token
_) : [Located Token]
ts)
= case SrcSpan
span of
UnhelpfulSpan FastString
_ -> (Located Token
t,FilePath
"") (Located Token, FilePath)
-> [(Located Token, FilePath)] -> [(Located Token, FilePath)]
forall a. a -> [a] -> [a]
: RealSrcLoc
-> InputFileBuffer
-> [Located Token]
-> [(Located Token, FilePath)]
addSourceToTokens RealSrcLoc
loc InputFileBuffer
buf [Located Token]
ts
RealSrcSpan RealSrcSpan
s Maybe BufSpan
_ -> (Located Token
t,FilePath
str) (Located Token, FilePath)
-> [(Located Token, FilePath)] -> [(Located Token, FilePath)]
forall a. a -> [a] -> [a]
: RealSrcLoc
-> InputFileBuffer
-> [Located Token]
-> [(Located Token, FilePath)]
addSourceToTokens RealSrcLoc
newLoc InputFileBuffer
newBuf [Located Token]
ts
where
(RealSrcLoc
newLoc, InputFileBuffer
newBuf, FilePath
str) = FilePath
-> RealSrcLoc
-> InputFileBuffer
-> (RealSrcLoc, InputFileBuffer, FilePath)
go FilePath
"" RealSrcLoc
loc InputFileBuffer
buf
start :: RealSrcLoc
start = RealSrcSpan -> RealSrcLoc
realSrcSpanStart RealSrcSpan
s
end :: RealSrcLoc
end = RealSrcSpan -> RealSrcLoc
realSrcSpanEnd RealSrcSpan
s
go :: FilePath
-> RealSrcLoc
-> InputFileBuffer
-> (RealSrcLoc, InputFileBuffer, FilePath)
go FilePath
acc RealSrcLoc
loc InputFileBuffer
buf | RealSrcLoc
loc RealSrcLoc -> RealSrcLoc -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord RealSrcLoc
< RealSrcLoc
start = FilePath
-> RealSrcLoc
-> InputFileBuffer
-> (RealSrcLoc, InputFileBuffer, FilePath)
go FilePath
acc RealSrcLoc
nLoc InputFileBuffer
nBuf
| RealSrcLoc
start RealSrcLoc -> RealSrcLoc -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord RealSrcLoc
<= RealSrcLoc
loc Bool -> Bool -> Bool
&& RealSrcLoc
loc RealSrcLoc -> RealSrcLoc -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord RealSrcLoc
< RealSrcLoc
end = FilePath
-> RealSrcLoc
-> InputFileBuffer
-> (RealSrcLoc, InputFileBuffer, FilePath)
go (Char
chChar -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:FilePath
acc) RealSrcLoc
nLoc InputFileBuffer
nBuf
| Bool
otherwise = (RealSrcLoc
loc, InputFileBuffer
buf, FilePath -> FilePath
forall a. [a] -> [a]
reverse FilePath
acc)
where (Char
ch, InputFileBuffer
nBuf) = InputFileBuffer -> (Char, InputFileBuffer)
nextChar InputFileBuffer
buf
nLoc :: RealSrcLoc
nLoc = RealSrcLoc -> Char -> RealSrcLoc
advanceSrcLoc RealSrcLoc
loc Char
ch
showRichTokenStream :: [(Located Token, String)] -> String
showRichTokenStream :: [(Located Token, FilePath)] -> FilePath
showRichTokenStream [(Located Token, FilePath)]
ts = RealSrcLoc -> [(Located Token, FilePath)] -> FilePath -> FilePath
forall {e}.
RealSrcLoc
-> [(GenLocated SrcSpan e, FilePath)] -> FilePath -> FilePath
go RealSrcLoc
startLoc [(Located Token, FilePath)]
ts FilePath
""
where sourceFile :: FastString
sourceFile = [SrcSpan] -> FastString
getFile ([SrcSpan] -> FastString) -> [SrcSpan] -> FastString
forall a b. (a -> b) -> a -> b
$ ((Located Token, FilePath) -> SrcSpan)
-> [(Located Token, FilePath)] -> [SrcSpan]
forall a b. (a -> b) -> [a] -> [b]
map (Located Token -> SrcSpan
forall l e. GenLocated l e -> l
getLoc (Located Token -> SrcSpan)
-> ((Located Token, FilePath) -> Located Token)
-> (Located Token, FilePath)
-> SrcSpan
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Located Token, FilePath) -> Located Token
forall a b. (a, b) -> a
fst) [(Located Token, FilePath)]
ts
getFile :: [SrcSpan] -> FastString
getFile [] = FilePath -> FastString
forall a. FilePath -> a
panic FilePath
"showRichTokenStream: No source file found"
getFile (UnhelpfulSpan FastString
_ : [SrcSpan]
xs) = [SrcSpan] -> FastString
getFile [SrcSpan]
xs
getFile (RealSrcSpan RealSrcSpan
s Maybe BufSpan
_ : [SrcSpan]
_) = RealSrcSpan -> FastString
srcSpanFile RealSrcSpan
s
startLoc :: RealSrcLoc
startLoc = FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc FastString
sourceFile Int
1 Int
1
go :: RealSrcLoc
-> [(GenLocated SrcSpan e, FilePath)] -> FilePath -> FilePath
go RealSrcLoc
_ [] = FilePath -> FilePath
forall a. a -> a
id
go RealSrcLoc
loc ((L SrcSpan
span e
_, FilePath
str):[(GenLocated SrcSpan e, FilePath)]
ts)
= case SrcSpan
span of
UnhelpfulSpan FastString
_ -> RealSrcLoc
-> [(GenLocated SrcSpan e, FilePath)] -> FilePath -> FilePath
go RealSrcLoc
loc [(GenLocated SrcSpan e, FilePath)]
ts
RealSrcSpan RealSrcSpan
s Maybe BufSpan
_
| Int
locLine Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
== Int
tokLine -> ((Int -> Char -> FilePath
forall a. Int -> a -> [a]
replicate (Int
tokCol Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
locCol) Char
' ') FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++)
(FilePath -> FilePath)
-> (FilePath -> FilePath) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath
str FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++)
(FilePath -> FilePath)
-> (FilePath -> FilePath) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RealSrcLoc
-> [(GenLocated SrcSpan e, FilePath)] -> FilePath -> FilePath
go RealSrcLoc
tokEnd [(GenLocated SrcSpan e, FilePath)]
ts
| Bool
otherwise -> ((Int -> Char -> FilePath
forall a. Int -> a -> [a]
replicate (Int
tokLine Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
locLine) Char
'\n') FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++)
(FilePath -> FilePath)
-> (FilePath -> FilePath) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int -> Char -> FilePath
forall a. Int -> a -> [a]
replicate (Int
tokCol Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1) Char
' ') FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++)
(FilePath -> FilePath)
-> (FilePath -> FilePath) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath
str FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++)
(FilePath -> FilePath)
-> (FilePath -> FilePath) -> FilePath -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RealSrcLoc
-> [(GenLocated SrcSpan e, FilePath)] -> FilePath -> FilePath
go RealSrcLoc
tokEnd [(GenLocated SrcSpan e, FilePath)]
ts
where (Int
locLine, Int
locCol) = (RealSrcLoc -> Int
srcLocLine RealSrcLoc
loc, RealSrcLoc -> Int
srcLocCol RealSrcLoc
loc)
(Int
tokLine, Int
tokCol) = (RealSrcSpan -> Int
srcSpanStartLine RealSrcSpan
s, RealSrcSpan -> Int
srcSpanStartCol RealSrcSpan
s)
tokEnd :: RealSrcLoc
tokEnd = RealSrcSpan -> RealSrcLoc
realSrcSpanEnd RealSrcSpan
s
findModule :: GhcMonad m => ModuleName -> Maybe FastString -> m Module
findModule :: ModuleName -> Maybe FastString -> m Module
findModule ModuleName
mod_name Maybe FastString
maybe_pkg = (HscEnv -> m Module) -> m Module
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSession ((HscEnv -> m Module) -> m Module)
-> (HscEnv -> m Module) -> m Module
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> do
let
dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
this_pkg :: Unit
this_pkg = DynFlags -> Unit
thisPackage DynFlags
dflags
case Maybe FastString
maybe_pkg of
Just FastString
pkg | FastString -> Unit
fsToUnit FastString
pkg Unit -> Unit -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Unit
/= Unit
this_pkg Bool -> Bool -> Bool
&& FastString
pkg FastString -> FastString -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq FastString
/= FilePath -> FastString
fsLit FilePath
"this" -> IO Module -> m Module
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO Module -> m Module) -> IO Module -> m Module
forall a b. (a -> b) -> a -> b
$ do
FindResult
res <- HscEnv -> ModuleName -> Maybe FastString -> IO FindResult
findImportedModule HscEnv
hsc_env ModuleName
mod_name Maybe FastString
maybe_pkg
case FindResult
res of
Found ModLocation
_ Module
m -> Module -> IO Module
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return Module
m
FindResult
err -> WarnMsg -> IO Module
forall (io :: * -> *) a. MonadIO io => WarnMsg -> io a
External instance of the constraint type MonadIO IO
throwOneError (WarnMsg -> IO Module) -> WarnMsg -> IO Module
forall a b. (a -> b) -> a -> b
$ DynFlags -> SrcSpan -> ModuleName -> FindResult -> WarnMsg
noModError DynFlags
dflags SrcSpan
noSrcSpan ModuleName
mod_name FindResult
err
Maybe FastString
_otherwise -> do
Maybe Module
home <- ModuleName -> m (Maybe Module)
forall (m :: * -> *). GhcMonad m => ModuleName -> m (Maybe Module)
Evidence bound by a type signature of the constraint type GhcMonad m
lookupLoadedHomeModule ModuleName
mod_name
case Maybe Module
home of
Just Module
m -> Module -> m Module
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return Module
m
Maybe Module
Nothing -> IO Module -> m Module
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO Module -> m Module) -> IO Module -> m Module
forall a b. (a -> b) -> a -> b
$ do
FindResult
res <- HscEnv -> ModuleName -> Maybe FastString -> IO FindResult
findImportedModule HscEnv
hsc_env ModuleName
mod_name Maybe FastString
maybe_pkg
case FindResult
res of
Found ModLocation
loc Module
m | Module -> Unit
forall unit. GenModule unit -> unit
moduleUnit Module
m Unit -> Unit -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Unit
/= Unit
this_pkg -> Module -> IO Module
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return Module
m
| Bool
otherwise -> DynFlags -> Module -> ModLocation -> IO Module
forall a. DynFlags -> Module -> ModLocation -> IO a
modNotLoadedError DynFlags
dflags Module
m ModLocation
loc
FindResult
err -> WarnMsg -> IO Module
forall (io :: * -> *) a. MonadIO io => WarnMsg -> io a
External instance of the constraint type MonadIO IO
throwOneError (WarnMsg -> IO Module) -> WarnMsg -> IO Module
forall a b. (a -> b) -> a -> b
$ DynFlags -> SrcSpan -> ModuleName -> FindResult -> WarnMsg
noModError DynFlags
dflags SrcSpan
noSrcSpan ModuleName
mod_name FindResult
err
modNotLoadedError :: DynFlags -> Module -> ModLocation -> IO a
modNotLoadedError :: DynFlags -> Module -> ModLocation -> IO a
modNotLoadedError DynFlags
dflags Module
m ModLocation
loc = GhcException -> IO a
forall a. GhcException -> IO a
throwGhcExceptionIO (GhcException -> IO a) -> GhcException -> IO a
forall a b. (a -> b) -> a -> b
$ FilePath -> GhcException
CmdLineError (FilePath -> GhcException) -> FilePath -> GhcException
forall a b. (a -> b) -> a -> b
$ DynFlags -> SDoc -> FilePath
showSDoc DynFlags
dflags (SDoc -> FilePath) -> SDoc -> FilePath
forall a b. (a -> b) -> a -> b
$
FilePath -> SDoc
text FilePath
"module is not loaded:" SDoc -> SDoc -> SDoc
<+>
SDoc -> SDoc
quotes (ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable ModuleName
ppr (Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
m)) SDoc -> SDoc -> SDoc
<+>
SDoc -> SDoc
parens (FilePath -> SDoc
text (FilePath -> Maybe FilePath -> FilePath
forall a. HasCallStack => FilePath -> Maybe a -> a
expectJust FilePath
"modNotLoadedError" (ModLocation -> Maybe FilePath
ml_hs_file ModLocation
loc)))
lookupModule :: GhcMonad m => ModuleName -> Maybe FastString -> m Module
lookupModule :: ModuleName -> Maybe FastString -> m Module
lookupModule ModuleName
mod_name (Just FastString
pkg) = ModuleName -> Maybe FastString -> m Module
forall (m :: * -> *).
GhcMonad m =>
ModuleName -> Maybe FastString -> m Module
Evidence bound by a type signature of the constraint type GhcMonad m
findModule ModuleName
mod_name (FastString -> Maybe FastString
forall a. a -> Maybe a
Just FastString
pkg)
lookupModule ModuleName
mod_name Maybe FastString
Nothing = (HscEnv -> m Module) -> m Module
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSession ((HscEnv -> m Module) -> m Module)
-> (HscEnv -> m Module) -> m Module
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> do
Maybe Module
home <- ModuleName -> m (Maybe Module)
forall (m :: * -> *). GhcMonad m => ModuleName -> m (Maybe Module)
Evidence bound by a type signature of the constraint type GhcMonad m
lookupLoadedHomeModule ModuleName
mod_name
case Maybe Module
home of
Just Module
m -> Module -> m Module
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return Module
m
Maybe Module
Nothing -> IO Module -> m Module
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO Module -> m Module) -> IO Module -> m Module
forall a b. (a -> b) -> a -> b
$ do
FindResult
res <- HscEnv -> ModuleName -> Maybe FastString -> IO FindResult
findExposedPackageModule HscEnv
hsc_env ModuleName
mod_name Maybe FastString
forall a. Maybe a
Nothing
case FindResult
res of
Found ModLocation
_ Module
m -> Module -> IO Module
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return Module
m
FindResult
err -> WarnMsg -> IO Module
forall (io :: * -> *) a. MonadIO io => WarnMsg -> io a
External instance of the constraint type MonadIO IO
throwOneError (WarnMsg -> IO Module) -> WarnMsg -> IO Module
forall a b. (a -> b) -> a -> b
$ DynFlags -> SrcSpan -> ModuleName -> FindResult -> WarnMsg
noModError (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env) SrcSpan
noSrcSpan ModuleName
mod_name FindResult
err
lookupLoadedHomeModule :: GhcMonad m => ModuleName -> m (Maybe Module)
lookupLoadedHomeModule :: ModuleName -> m (Maybe Module)
lookupLoadedHomeModule ModuleName
mod_name = (HscEnv -> m (Maybe Module)) -> m (Maybe Module)
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSession ((HscEnv -> m (Maybe Module)) -> m (Maybe Module))
-> (HscEnv -> m (Maybe Module)) -> m (Maybe Module)
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env ->
case HomePackageTable -> ModuleName -> Maybe HomeModInfo
lookupHpt (HscEnv -> HomePackageTable
hsc_HPT HscEnv
hsc_env) ModuleName
mod_name of
Just HomeModInfo
mod_info -> Maybe Module -> m (Maybe Module)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (Module -> Maybe Module
forall a. a -> Maybe a
Just (ModIface -> Module
forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module (HomeModInfo -> ModIface
hm_iface HomeModInfo
mod_info)))
Maybe HomeModInfo
_not_a_home_module -> Maybe Module -> m (Maybe Module)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return Maybe Module
forall a. Maybe a
Nothing
isModuleTrusted :: GhcMonad m => Module -> m Bool
isModuleTrusted :: Module -> m Bool
isModuleTrusted Module
m = (HscEnv -> m Bool) -> m Bool
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSession ((HscEnv -> m Bool) -> m Bool) -> (HscEnv -> m Bool) -> m Bool
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env ->
IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ HscEnv -> Module -> SrcSpan -> IO Bool
hscCheckSafe HscEnv
hsc_env Module
m SrcSpan
noSrcSpan
moduleTrustReqs :: GhcMonad m => Module -> m (Bool, Set UnitId)
moduleTrustReqs :: Module -> m (Bool, Set UnitId)
moduleTrustReqs Module
m = (HscEnv -> m (Bool, Set UnitId)) -> m (Bool, Set UnitId)
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSession ((HscEnv -> m (Bool, Set UnitId)) -> m (Bool, Set UnitId))
-> (HscEnv -> m (Bool, Set UnitId)) -> m (Bool, Set UnitId)
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env ->
IO (Bool, Set UnitId) -> m (Bool, Set UnitId)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO (Bool, Set UnitId) -> m (Bool, Set UnitId))
-> IO (Bool, Set UnitId) -> m (Bool, Set UnitId)
forall a b. (a -> b) -> a -> b
$ HscEnv -> Module -> SrcSpan -> IO (Bool, Set UnitId)
hscGetSafe HscEnv
hsc_env Module
m SrcSpan
noSrcSpan
setGHCiMonad :: GhcMonad m => String -> m ()
setGHCiMonad :: FilePath -> m ()
setGHCiMonad FilePath
name = (HscEnv -> m ()) -> m ()
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSession ((HscEnv -> m ()) -> m ()) -> (HscEnv -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> do
Name
ty <- IO Name -> m Name
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO Name -> m Name) -> IO Name -> m Name
forall a b. (a -> b) -> a -> b
$ HscEnv -> FilePath -> IO Name
hscIsGHCiMonad HscEnv
hsc_env FilePath
name
(HscEnv -> HscEnv) -> m ()
forall (m :: * -> *). GhcMonad m => (HscEnv -> HscEnv) -> m ()
Evidence bound by a type signature of the constraint type GhcMonad m
modifySession ((HscEnv -> HscEnv) -> m ()) -> (HscEnv -> HscEnv) -> m ()
forall a b. (a -> b) -> a -> b
$ \HscEnv
s ->
let ic :: InteractiveContext
ic = (HscEnv -> InteractiveContext
hsc_IC HscEnv
s) { ic_monad :: Name
ic_monad = Name
ty }
in HscEnv
s { hsc_IC :: InteractiveContext
hsc_IC = InteractiveContext
ic }
getGHCiMonad :: GhcMonad m => m Name
getGHCiMonad :: m Name
getGHCiMonad = (HscEnv -> Name) -> m HscEnv -> m Name
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (m :: * -> *). GhcMonad m => Functor m
Evidence bound by a type signature of the constraint type GhcMonad m
fmap (InteractiveContext -> Name
ic_monad (InteractiveContext -> Name)
-> (HscEnv -> InteractiveContext) -> HscEnv -> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HscEnv -> InteractiveContext
hsc_IC) m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
Evidence bound by a type signature of the constraint type GhcMonad m
getSession
getHistorySpan :: GhcMonad m => History -> m SrcSpan
getHistorySpan :: History -> m SrcSpan
getHistorySpan History
h = (HscEnv -> m SrcSpan) -> m SrcSpan
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSession ((HscEnv -> m SrcSpan) -> m SrcSpan)
-> (HscEnv -> m SrcSpan) -> m SrcSpan
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env ->
SrcSpan -> m SrcSpan
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (SrcSpan -> m SrcSpan) -> SrcSpan -> m SrcSpan
forall a b. (a -> b) -> a -> b
$ HscEnv -> History -> SrcSpan
GHC.Runtime.Eval.getHistorySpan HscEnv
hsc_env History
h
obtainTermFromVal :: GhcMonad m => Int -> Bool -> Type -> a -> m Term
obtainTermFromVal :: Int -> Bool -> Type -> a -> m Term
obtainTermFromVal Int
bound Bool
force Type
ty a
a = (HscEnv -> m Term) -> m Term
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSession ((HscEnv -> m Term) -> m Term) -> (HscEnv -> m Term) -> m Term
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env ->
IO Term -> m Term
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO Term -> m Term) -> IO Term -> m Term
forall a b. (a -> b) -> a -> b
$ HscEnv -> Int -> Bool -> Type -> a -> IO Term
forall a. HscEnv -> Int -> Bool -> Type -> a -> IO Term
GHC.Runtime.Eval.obtainTermFromVal HscEnv
hsc_env Int
bound Bool
force Type
ty a
a
obtainTermFromId :: GhcMonad m => Int -> Bool -> Id -> m Term
obtainTermFromId :: Int -> Bool -> Var -> m Term
obtainTermFromId Int
bound Bool
force Var
id = (HscEnv -> m Term) -> m Term
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSession ((HscEnv -> m Term) -> m Term) -> (HscEnv -> m Term) -> m Term
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env ->
IO Term -> m Term
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO Term -> m Term) -> IO Term -> m Term
forall a b. (a -> b) -> a -> b
$ HscEnv -> Int -> Bool -> Var -> IO Term
GHC.Runtime.Eval.obtainTermFromId HscEnv
hsc_env Int
bound Bool
force Var
id
lookupName :: GhcMonad m => Name -> m (Maybe TyThing)
lookupName :: Name -> m (Maybe TyThing)
lookupName Name
name =
(HscEnv -> m (Maybe TyThing)) -> m (Maybe TyThing)
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSession ((HscEnv -> m (Maybe TyThing)) -> m (Maybe TyThing))
-> (HscEnv -> m (Maybe TyThing)) -> m (Maybe TyThing)
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env ->
IO (Maybe TyThing) -> m (Maybe TyThing)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
External instance of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO (Maybe TyThing) -> m (Maybe TyThing))
-> IO (Maybe TyThing) -> m (Maybe TyThing)
forall a b. (a -> b) -> a -> b
$ HscEnv -> Name -> IO (Maybe TyThing)
hscTcRcLookupName HscEnv
hsc_env Name
name
parser :: String
-> DynFlags
-> FilePath
-> (WarningMessages, Either ErrorMessages (Located HsModule))
parser :: FilePath
-> DynFlags
-> FilePath
-> (Bag WarnMsg, Either (Bag WarnMsg) ParsedSource)
parser FilePath
str DynFlags
dflags FilePath
filename =
let
loc :: RealSrcLoc
loc = FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc (FilePath -> FastString
mkFastString FilePath
filename) Int
1 Int
1
buf :: InputFileBuffer
buf = FilePath -> InputFileBuffer
stringToStringBuffer FilePath
str
in
case P ParsedSource -> PState -> ParseResult ParsedSource
forall a. P a -> PState -> ParseResult a
unP P ParsedSource
Parser.parseModule (DynFlags -> InputFileBuffer -> RealSrcLoc -> PState
mkPState DynFlags
dflags InputFileBuffer
buf RealSrcLoc
loc) of
PFailed PState
pst ->
let (Bag WarnMsg
warns,Bag WarnMsg
errs) = PState -> DynFlags -> Messages
getMessages PState
pst DynFlags
dflags in
(Bag WarnMsg
warns, Bag WarnMsg -> Either (Bag WarnMsg) ParsedSource
forall a b. a -> Either a b
Left Bag WarnMsg
errs)
POk PState
pst ParsedSource
rdr_module ->
let (Bag WarnMsg
warns,Bag WarnMsg
_) = PState -> DynFlags -> Messages
getMessages PState
pst DynFlags
dflags in
(Bag WarnMsg
warns, ParsedSource -> Either (Bag WarnMsg) ParsedSource
forall a b. b -> Either a b
Right ParsedSource
rdr_module)
interpretPackageEnv :: DynFlags -> IO DynFlags
interpretPackageEnv :: DynFlags -> IO DynFlags
interpretPackageEnv DynFlags
dflags = do
Maybe FilePath
mPkgEnv <- MaybeT IO FilePath -> IO (Maybe FilePath)
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (MaybeT IO FilePath -> IO (Maybe FilePath))
-> MaybeT IO FilePath -> IO (Maybe FilePath)
forall a b. (a -> b) -> a -> b
$ [MaybeT IO FilePath] -> MaybeT IO FilePath
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
External instance of the constraint type forall (m :: * -> *). Monad m => MonadPlus (MaybeT m)
External instance of the constraint type Monad IO
External instance of the constraint type Foldable []
msum ([MaybeT IO FilePath] -> MaybeT IO FilePath)
-> [MaybeT IO FilePath] -> MaybeT IO FilePath
forall a b. (a -> b) -> a -> b
$ [
MaybeT IO FilePath
getCmdLineArg MaybeT IO FilePath
-> (FilePath -> MaybeT IO FilePath) -> MaybeT IO FilePath
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
External instance of the constraint type forall (m :: * -> *). Monad m => Monad (MaybeT m)
External instance of the constraint type Monad IO
>>= \FilePath
env -> [MaybeT IO FilePath] -> MaybeT IO FilePath
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
External instance of the constraint type forall (m :: * -> *). Monad m => MonadPlus (MaybeT m)
External instance of the constraint type Monad IO
External instance of the constraint type Foldable []
msum [
FilePath -> MaybeT IO FilePath
probeNullEnv FilePath
env
, FilePath -> MaybeT IO FilePath
probeEnvFile FilePath
env
, FilePath -> MaybeT IO FilePath
probeEnvName FilePath
env
, FilePath -> MaybeT IO FilePath
forall a. FilePath -> MaybeT IO a
cmdLineError FilePath
env
]
, MaybeT IO FilePath
getEnvVar MaybeT IO FilePath
-> (FilePath -> MaybeT IO FilePath) -> MaybeT IO FilePath
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
External instance of the constraint type forall (m :: * -> *). Monad m => Monad (MaybeT m)
External instance of the constraint type Monad IO
>>= \FilePath
env -> [MaybeT IO FilePath] -> MaybeT IO FilePath
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
External instance of the constraint type forall (m :: * -> *). Monad m => MonadPlus (MaybeT m)
External instance of the constraint type Monad IO
External instance of the constraint type Foldable []
msum [
FilePath -> MaybeT IO FilePath
probeNullEnv FilePath
env
, FilePath -> MaybeT IO FilePath
probeEnvFile FilePath
env
, FilePath -> MaybeT IO FilePath
probeEnvName FilePath
env
, FilePath -> MaybeT IO FilePath
forall a. FilePath -> MaybeT IO a
envError FilePath
env
]
, MaybeT IO ()
notIfHideAllPackages MaybeT IO () -> MaybeT IO FilePath -> MaybeT IO FilePath
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type forall (m :: * -> *). Monad m => Monad (MaybeT m)
External instance of the constraint type Monad IO
>> [MaybeT IO FilePath] -> MaybeT IO FilePath
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
External instance of the constraint type forall (m :: * -> *). Monad m => MonadPlus (MaybeT m)
External instance of the constraint type Monad IO
External instance of the constraint type Foldable []
msum [
MaybeT IO FilePath
findLocalEnvFile MaybeT IO FilePath
-> (FilePath -> MaybeT IO FilePath) -> MaybeT IO FilePath
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
External instance of the constraint type forall (m :: * -> *). Monad m => Monad (MaybeT m)
External instance of the constraint type Monad IO
>>= FilePath -> MaybeT IO FilePath
probeEnvFile
, FilePath -> MaybeT IO FilePath
probeEnvName FilePath
defaultEnvName
]
]
case Maybe FilePath
mPkgEnv of
Maybe FilePath
Nothing ->
DynFlags -> IO DynFlags
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return DynFlags
dflags
Just FilePath
"-" -> do
DynFlags -> IO DynFlags
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return DynFlags
dflags
Just FilePath
envfile -> do
FilePath
content <- FilePath -> IO FilePath
readFile FilePath
envfile
DynFlags -> FatalMessager
compilationProgressMsg DynFlags
dflags (FilePath
"Loaded package environment from " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
envfile)
let ((Errs, Warns, ())
_, DynFlags
dflags') = CmdLineP DynFlags (Errs, Warns, ())
-> DynFlags -> ((Errs, Warns, ()), DynFlags)
forall s a. CmdLineP s a -> s -> (a, s)
runCmdLine (EwM (CmdLineP DynFlags) () -> CmdLineP DynFlags (Errs, Warns, ())
forall (m :: * -> *) a. EwM m a -> m (Errs, Warns, a)
runEwM (FilePath -> FilePath -> EwM (CmdLineP DynFlags) ()
setFlagsFromEnvFile FilePath
envfile FilePath
content)) DynFlags
dflags
DynFlags -> IO DynFlags
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return DynFlags
dflags'
where
namedEnvPath :: String -> MaybeT IO FilePath
namedEnvPath :: FilePath -> MaybeT IO FilePath
namedEnvPath FilePath
name = do
FilePath
appdir <- DynFlags -> MaybeT IO FilePath
versionedAppDir DynFlags
dflags
FilePath -> MaybeT IO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). Monad m => Monad (MaybeT m)
External instance of the constraint type Monad IO
return (FilePath -> MaybeT IO FilePath) -> FilePath -> MaybeT IO FilePath
forall a b. (a -> b) -> a -> b
$ FilePath
appdir FilePath -> FilePath -> FilePath
</> FilePath
"environments" FilePath -> FilePath -> FilePath
</> FilePath
name
probeEnvName :: String -> MaybeT IO FilePath
probeEnvName :: FilePath -> MaybeT IO FilePath
probeEnvName FilePath
name = FilePath -> MaybeT IO FilePath
probeEnvFile (FilePath -> MaybeT IO FilePath)
-> MaybeT IO FilePath -> MaybeT IO FilePath
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
External instance of the constraint type forall (m :: * -> *). Monad m => Monad (MaybeT m)
External instance of the constraint type Monad IO
=<< FilePath -> MaybeT IO FilePath
namedEnvPath FilePath
name
probeEnvFile :: FilePath -> MaybeT IO FilePath
probeEnvFile :: FilePath -> MaybeT IO FilePath
probeEnvFile FilePath
path = do
Bool -> MaybeT IO ()
forall (f :: * -> *). Alternative f => Bool -> f ()
External instance of the constraint type forall (m :: * -> *).
(Functor m, Monad m) =>
Alternative (MaybeT m)
External instance of the constraint type Functor IO
External instance of the constraint type Monad IO
guard (Bool -> MaybeT IO ()) -> MaybeT IO Bool -> MaybeT IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
External instance of the constraint type forall (m :: * -> *). Monad m => Monad (MaybeT m)
External instance of the constraint type Monad IO
=<< IO Bool -> MaybeT IO Bool
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
External instance of the constraint type Monad IO
liftMaybeT (FilePath -> IO Bool
doesFileExist FilePath
path)
FilePath -> MaybeT IO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). Monad m => Monad (MaybeT m)
External instance of the constraint type Monad IO
return FilePath
path
probeNullEnv :: FilePath -> MaybeT IO FilePath
probeNullEnv :: FilePath -> MaybeT IO FilePath
probeNullEnv FilePath
"-" = FilePath -> MaybeT IO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). Monad m => Monad (MaybeT m)
External instance of the constraint type Monad IO
return FilePath
"-"
probeNullEnv FilePath
_ = MaybeT IO FilePath
forall (m :: * -> *) a. MonadPlus m => m a
External instance of the constraint type forall (m :: * -> *). Monad m => MonadPlus (MaybeT m)
External instance of the constraint type Monad IO
mzero
getCmdLineArg :: MaybeT IO String
getCmdLineArg :: MaybeT IO FilePath
getCmdLineArg = IO (Maybe FilePath) -> MaybeT IO FilePath
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (IO (Maybe FilePath) -> MaybeT IO FilePath)
-> IO (Maybe FilePath) -> MaybeT IO FilePath
forall a b. (a -> b) -> a -> b
$ Maybe FilePath -> IO (Maybe FilePath)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return (Maybe FilePath -> IO (Maybe FilePath))
-> Maybe FilePath -> IO (Maybe FilePath)
forall a b. (a -> b) -> a -> b
$ DynFlags -> Maybe FilePath
packageEnv DynFlags
dflags
getEnvVar :: MaybeT IO String
getEnvVar :: MaybeT IO FilePath
getEnvVar = do
Either IOError FilePath
mvar <- IO (Either IOError FilePath) -> MaybeT IO (Either IOError FilePath)
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
External instance of the constraint type Monad IO
liftMaybeT (IO (Either IOError FilePath)
-> MaybeT IO (Either IOError FilePath))
-> IO (Either IOError FilePath)
-> MaybeT IO (Either IOError FilePath)
forall a b. (a -> b) -> a -> b
$ IO FilePath -> IO (Either IOError FilePath)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> m (Either e a)
External instance of the constraint type Exception IOError
External instance of the constraint type MonadCatch IO
MC.try (IO FilePath -> IO (Either IOError FilePath))
-> IO FilePath -> IO (Either IOError FilePath)
forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
getEnv FilePath
"GHC_ENVIRONMENT"
case Either IOError FilePath
mvar of
Right FilePath
var -> FilePath -> MaybeT IO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). Monad m => Monad (MaybeT m)
External instance of the constraint type Monad IO
return FilePath
var
Left IOError
err -> if IOError -> Bool
isDoesNotExistError IOError
err then MaybeT IO FilePath
forall (m :: * -> *) a. MonadPlus m => m a
External instance of the constraint type forall (m :: * -> *). Monad m => MonadPlus (MaybeT m)
External instance of the constraint type Monad IO
mzero
else IO FilePath -> MaybeT IO FilePath
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
External instance of the constraint type Monad IO
liftMaybeT (IO FilePath -> MaybeT IO FilePath)
-> IO FilePath -> MaybeT IO FilePath
forall a b. (a -> b) -> a -> b
$ IOError -> IO FilePath
forall e a. Exception e => e -> IO a
External instance of the constraint type Exception IOError
throwIO IOError
err
notIfHideAllPackages :: MaybeT IO ()
notIfHideAllPackages :: MaybeT IO ()
notIfHideAllPackages =
Bool -> MaybeT IO ()
forall (f :: * -> *). Alternative f => Bool -> f ()
External instance of the constraint type forall (m :: * -> *).
(Functor m, Monad m) =>
Alternative (MaybeT m)
External instance of the constraint type Functor IO
External instance of the constraint type Monad IO
guard (Bool -> Bool
not (GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_HideAllPackages DynFlags
dflags))
defaultEnvName :: String
defaultEnvName :: FilePath
defaultEnvName = FilePath
"default"
localEnvFileName :: FilePath
localEnvFileName :: FilePath
localEnvFileName = FilePath
".ghc.environment" FilePath -> FilePath -> FilePath
<.> DynFlags -> FilePath
versionedFilePath DynFlags
dflags
findLocalEnvFile :: MaybeT IO FilePath
findLocalEnvFile :: MaybeT IO FilePath
findLocalEnvFile = do
FilePath
curdir <- IO FilePath -> MaybeT IO FilePath
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
External instance of the constraint type Monad IO
liftMaybeT IO FilePath
getCurrentDirectory
FilePath
homedir <- IO FilePath -> MaybeT IO FilePath
forall a. IO a -> MaybeT IO a
tryMaybeT IO FilePath
getHomeDirectory
let probe :: FilePath -> MaybeT IO FilePath
probe FilePath
dir | FilePath -> Bool
isDrive FilePath
dir Bool -> Bool -> Bool
|| FilePath
dir FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
== FilePath
homedir
= MaybeT IO FilePath
forall (m :: * -> *) a. MonadPlus m => m a
External instance of the constraint type forall (m :: * -> *). Monad m => MonadPlus (MaybeT m)
External instance of the constraint type Monad IO
mzero
probe FilePath
dir = do
let file :: FilePath
file = FilePath
dir FilePath -> FilePath -> FilePath
</> FilePath
localEnvFileName
Bool
exists <- IO Bool -> MaybeT IO Bool
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
External instance of the constraint type Monad IO
liftMaybeT (FilePath -> IO Bool
doesFileExist FilePath
file)
if Bool
exists
then FilePath -> MaybeT IO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). Monad m => Monad (MaybeT m)
External instance of the constraint type Monad IO
return FilePath
file
else FilePath -> MaybeT IO FilePath
probe (FilePath -> FilePath
takeDirectory FilePath
dir)
FilePath -> MaybeT IO FilePath
probe FilePath
curdir
cmdLineError :: String -> MaybeT IO a
cmdLineError :: FilePath -> MaybeT IO a
cmdLineError FilePath
env = IO a -> MaybeT IO a
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
External instance of the constraint type Monad IO
liftMaybeT (IO a -> MaybeT IO a)
-> (FilePath -> IO a) -> FilePath -> MaybeT IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GhcException -> IO a
forall a. GhcException -> IO a
throwGhcExceptionIO (GhcException -> IO a)
-> (FilePath -> GhcException) -> FilePath -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> GhcException
CmdLineError (FilePath -> MaybeT IO a) -> FilePath -> MaybeT IO a
forall a b. (a -> b) -> a -> b
$
FilePath
"Package environment " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath -> FilePath
forall a. Show a => a -> FilePath
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
show FilePath
env FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" not found"
envError :: String -> MaybeT IO a
envError :: FilePath -> MaybeT IO a
envError FilePath
env = IO a -> MaybeT IO a
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
External instance of the constraint type Monad IO
liftMaybeT (IO a -> MaybeT IO a)
-> (FilePath -> IO a) -> FilePath -> MaybeT IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GhcException -> IO a
forall a. GhcException -> IO a
throwGhcExceptionIO (GhcException -> IO a)
-> (FilePath -> GhcException) -> FilePath -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> GhcException
CmdLineError (FilePath -> MaybeT IO a) -> FilePath -> MaybeT IO a
forall a b. (a -> b) -> a -> b
$
FilePath
"Package environment "
FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath -> FilePath
forall a. Show a => a -> FilePath
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
show FilePath
env
FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" (specified in GHC_ENVIRONMENT) not found"