{-# 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(..), Backend(..), gopt,
GhcMode(..), GhcLink(..),
parseDynamicFlags, parseTargetFiles,
getSessionDynFlags, setSessionDynFlags,
getProgramDynFlags, setProgramDynFlags,
getInteractiveDynFlags, setInteractiveDynFlags,
interpretPackageEnv,
Logger, getLogger,
pushLogHook, popLogHook,
pushLogHookM, popLogHookM, modifyLogger,
putMsgM, putLogMsgM,
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(..),
GHC.Runtime.Eval.back,
GHC.Runtime.Eval.forward,
GHC.Runtime.Eval.setupBreakpoint,
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, dataConWrapperType,
dataConSrcBangs,
StrictnessMark(..), isMarkedStrict,
Class,
classMethods, classSCTheta, classTvsFds, classATs,
pprFundeps,
ClsInst,
instanceDFunId,
pprInstance, pprInstanceHdr,
pprFamInst,
FamInst,
Type, splitForAllTyCoVars, 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, RealLocated,
noLoc, mkGeneralLocated,
getLoc, unLoc,
getRealSrcSpan, unRealSrcSpan,
eqLocated, cmpLocated, combineLocs, addCLoc,
leftmost_smallest, leftmost_largest, rightmost_smallest,
spans, isSubspanOf,
GhcException(..), showGhcException,
GhcApiError(..),
Token,
getTokenStream, getRichTokenStream,
showRichTokenStream, addSourceToTokens,
parser,
AnnKeywordId(..),EpaComment(..),
cyclicModuleErr,
) where
#include "HsVersions.h"
import GHC.Prelude hiding (init)
import GHC.Platform
import GHC.Platform.Ways
import GHC.Driver.Phases ( Phase(..), isHaskellSrcFilename
, isSourceFilename, startPhase )
import GHC.Driver.Env
import GHC.Driver.Errors
import GHC.Driver.CmdLine
import GHC.Driver.Session hiding (WarnReason(..))
import GHC.Driver.Backend
import GHC.Driver.Config
import GHC.Driver.Main
import GHC.Driver.Make
import GHC.Driver.Hooks
import GHC.Driver.Pipeline ( compileOne' )
import GHC.Driver.Monad
import GHC.Driver.Ppr
import GHC.ByteCode.Types
import qualified GHC.Linker.Loader as Loader
import GHC.Runtime.Loader
import GHC.Runtime.Eval
import GHC.Runtime.Eval.Types
import GHC.Runtime.Interpreter
import GHC.Runtime.Context
import GHCi.RemoteTypes
import qualified GHC.Parser as Parser
import GHC.Parser.Lexer
import GHC.Parser.Annotation
import GHC.Parser.Errors.Ppr
import GHC.Parser.Utils
import GHC.Iface.Load ( loadSysInterface )
import GHC.Hs
import GHC.Builtin.Types.Prim ( alphaTyVars )
import GHC.Iface.Tidy
import GHC.Data.Bag ( listToBag )
import GHC.Data.StringBuffer
import GHC.Data.FastString
import qualified GHC.LanguageExtensions as LangExt
import GHC.Tc.Utils.Monad ( finalSafeMode, fixSafeInstances, initIfaceTcRn )
import GHC.Tc.Types
import GHC.Tc.Utils.TcType
import GHC.Tc.Module
import GHC.Tc.Utils.Instantiate
import GHC.Tc.Instance.Family
import GHC.Utils.TmpFs
import GHC.SysTools
import GHC.SysTools.BaseDir
import GHC.Utils.Error
import GHC.Utils.Monad
import GHC.Utils.Misc
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Utils.Logger
import GHC.Core.Predicate
import GHC.Core.Type hiding( typeKind )
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.Core
import GHC.Types.Id
import GHC.Types.Name hiding ( varName )
import GHC.Types.Avail
import GHC.Types.SrcLoc
import GHC.Types.TyThing.Ppr ( pprFamInst )
import GHC.Types.Annotations
import GHC.Types.Name.Set
import GHC.Types.Name.Reader
import GHC.Types.SourceError
import GHC.Types.SafeHaskell
import GHC.Types.Fixity
import GHC.Types.Target
import GHC.Types.Basic
import GHC.Types.TyThing
import GHC.Types.Name.Env
import GHC.Types.Name.Ppr
import GHC.Types.TypeEnv
import GHC.Types.SourceFile
import GHC.Unit
import GHC.Unit.Env
import GHC.Unit.External
import GHC.Unit.State
import GHC.Unit.Finder
import GHC.Unit.Module.ModIface
import GHC.Unit.Module.ModGuts
import GHC.Unit.Module.ModDetails
import GHC.Unit.Module.ModSummary
import GHC.Unit.Module.Graph
import GHC.Unit.Home.ModInfo
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
import Data.List (isPrefixOf)
defaultErrorHandler :: (ExceptionMonad m)
=> FatalMessager -> FlushOut -> m a -> m a
defaultErrorHandler :: forall (m :: * -> *) a.
ExceptionMonad m =>
FatalMessager -> FlushOut -> m a -> m a
defaultErrorHandler FatalMessager
fm (FlushOut IO ()
flushOut) m a
inner =
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
(e -> m a) -> m a -> m a
MC.handle (\SomeException
exception -> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
IO ()
flushOut
case forall e. Exception e => SomeException -> Maybe e
fromException SomeException
exception of
Just (IOError
ioe :: IOException) ->
FatalMessager -> FatalMessager
fatalErrorMsg'' FatalMessager
fm (forall a. Show a => a -> FilePath
show IOError
ioe)
Maybe IOError
_ -> case forall e. Exception e => SomeException -> Maybe e
fromException SomeException
exception of
Just AsyncException
UserInterrupt ->
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => e -> IO a
throwIO AsyncException
UserInterrupt
Just AsyncException
StackOverflow ->
FatalMessager -> FatalMessager
fatalErrorMsg'' FatalMessager
fm FilePath
"stack overflow: use +RTS -K<size> to increase it"
Maybe AsyncException
_ -> case forall e. Exception e => SomeException -> Maybe e
fromException SomeException
exception of
Just (ExitCode
ex :: ExitCode) -> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => e -> IO a
throwIO ExitCode
ex
Maybe ExitCode
_ ->
FatalMessager -> FatalMessager
fatalErrorMsg'' FatalMessager
fm
(forall a. Show a => a -> FilePath
show (FilePath -> GhcException
Panic (forall a. Show a => a -> FilePath
show SomeException
exception)))
forall a. ExitCode -> IO a
exitWith (Int -> ExitCode
ExitFailure Int
1)
) forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) a.
ExceptionMonad m =>
(GhcException -> m a) -> m a -> m a
handleGhcException
(\GhcException
ge -> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
IO ()
flushOut
case GhcException
ge of
Signal Int
_ -> forall a. ExitCode -> IO a
exitWith (Int -> ExitCode
ExitFailure Int
1)
GhcException
_ -> do FatalMessager -> FatalMessager
fatalErrorMsg'' FatalMessager
fm (forall a. Show a => a -> FilePath
show GhcException
ge)
forall a. ExitCode -> IO a
exitWith (Int -> ExitCode
ExitFailure Int
1)
) 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 :: forall (m :: * -> *) a. ExceptionMonad m => DynFlags -> m a -> m a
defaultCleanupHandler DynFlags
_ m a
m = m a
m
where _warning_suppression :: m a
_warning_suppression = m a
m forall (m :: * -> *) a b. MonadCatch m => m a -> m b -> m a
`MC.onException` forall a. HasCallStack => a
undefined
runGhc :: Maybe FilePath
-> Ghc a
-> IO a
runGhc :: forall a. Maybe FilePath -> Ghc a -> IO a
runGhc Maybe FilePath
mb_top_dir Ghc a
ghc = do
IORef HscEnv
ref <- forall a. a -> IO (IORef a)
newIORef (forall a. FilePath -> a
panic FilePath
"empty session")
let session :: Session
session = IORef HscEnv -> Session
Session IORef HscEnv
ref
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Ghc a -> Session -> IO a
unGhc Session
session forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. ExceptionMonad m => m a -> m a
withSignalHandlers forall a b. (a -> b) -> a -> b
$ do
forall (m :: * -> *). GhcMonad m => Maybe FilePath -> m ()
initGhcMonad Maybe FilePath
mb_top_dir
forall (m :: * -> *) a. GhcMonad m => m a -> m a
withCleanupSession Ghc a
ghc
runGhcT :: ExceptionMonad m =>
Maybe FilePath
-> GhcT m a
-> m a
runGhcT :: forall (m :: * -> *) a.
ExceptionMonad m =>
Maybe FilePath -> GhcT m a -> m a
runGhcT Maybe FilePath
mb_top_dir GhcT m a
ghct = do
IORef HscEnv
ref <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. a -> IO (IORef a)
newIORef (forall a. FilePath -> a
panic FilePath
"empty session")
let session :: Session
session = IORef HscEnv -> Session
Session IORef HscEnv
ref
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (m :: * -> *) a. GhcT m a -> Session -> m a
unGhcT Session
session forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. ExceptionMonad m => m a -> m a
withSignalHandlers forall a b. (a -> b) -> a -> b
$ do
forall (m :: * -> *). GhcMonad m => Maybe FilePath -> m ()
initGhcMonad Maybe FilePath
mb_top_dir
forall (m :: * -> *) a. GhcMonad m => m a -> m a
withCleanupSession GhcT m a
ghct
withCleanupSession :: GhcMonad m => m a -> m a
withCleanupSession :: forall (m :: * -> *) a. GhcMonad m => m a -> m a
withCleanupSession m a
ghc = m a
ghc forall (m :: * -> *) a b. MonadMask m => m a -> m b -> m a
`MC.finally` m ()
cleanup
where
cleanup :: m ()
cleanup = do
HscEnv
hsc_env <- forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
let logger :: Logger
logger = HscEnv -> Logger
hsc_logger HscEnv
hsc_env
let tmpfs :: TmpFs
tmpfs = HscEnv -> TmpFs
hsc_tmpfs HscEnv
hsc_env
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
Logger -> TmpFs -> DynFlags -> IO ()
cleanTempFiles Logger
logger TmpFs
tmpfs DynFlags
dflags
Logger -> TmpFs -> DynFlags -> IO ()
cleanTempDirs Logger
logger TmpFs
tmpfs DynFlags
dflags
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ Interp -> IO ()
stopInterp (HscEnv -> Maybe Interp
hsc_interp HscEnv
hsc_env)
initGhcMonad :: GhcMonad m => Maybe FilePath -> m ()
initGhcMonad :: forall (m :: * -> *). GhcMonad m => Maybe FilePath -> m ()
initGhcMonad Maybe FilePath
mb_top_dir
= do { HscEnv
env <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO 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)
; HscEnv
hsc_env <- DynFlags -> IO HscEnv
newHscEnv DynFlags
dflags
; forall (m :: * -> *). MonadIO m => Logger -> DynFlags -> m ()
checkBrokenTablesNextToCode (HscEnv -> Logger
hsc_logger HscEnv
hsc_env) DynFlags
dflags
; DynFlags -> IO ()
setUnsafeGlobalDynFlags DynFlags
dflags
; forall (m :: * -> *) a. Monad m => a -> m a
return HscEnv
hsc_env }
; forall (m :: * -> *). GhcMonad m => HscEnv -> m ()
setSession HscEnv
env }
checkBrokenTablesNextToCode :: MonadIO m => Logger -> DynFlags -> m ()
checkBrokenTablesNextToCode :: forall (m :: * -> *). MonadIO m => Logger -> DynFlags -> m ()
checkBrokenTablesNextToCode Logger
logger DynFlags
dflags
= do { Bool
broken <- forall (m :: * -> *). MonadIO m => Logger -> DynFlags -> m Bool
checkBrokenTablesNextToCode' Logger
logger DynFlags
dflags
; forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
broken
forall a b. (a -> b) -> a -> b
$ do { Any
_ <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ DynFlags -> SDoc -> GhcApiError
mkApiErr DynFlags
dflags SDoc
invalidLdErr
; forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadFail m => FilePath -> m a
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 => Logger -> DynFlags -> m Bool
checkBrokenTablesNextToCode' :: forall (m :: * -> *). MonadIO m => Logger -> DynFlags -> m Bool
checkBrokenTablesNextToCode' Logger
logger DynFlags
dflags
| Bool -> Bool
not (Arch -> Bool
isARM Arch
arch) = forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
| Way
WayDyn forall a. Ord a => a -> Set a -> Bool
`S.notMember` DynFlags -> Ways
ways DynFlags
dflags = forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
| Bool -> Bool
not Bool
tablesNextToCode = forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
| Bool
otherwise = do
LinkerInfo
linkerInfo <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ Logger -> DynFlags -> IO LinkerInfo
getLinkerInfo Logger
logger DynFlags
dflags
case LinkerInfo
linkerInfo of
GnuLD [Option]
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
LinkerInfo
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
where platform :: Platform
platform = DynFlags -> Platform
targetPlatform DynFlags
dflags
arch :: Arch
arch = Platform -> Arch
platformArch Platform
platform
tablesNextToCode :: Bool
tablesNextToCode = Platform -> Bool
platformTablesNextToCode Platform
platform
setSessionDynFlags :: GhcMonad m => DynFlags -> m ()
setSessionDynFlags :: forall (m :: * -> *). GhcMonad m => DynFlags -> m ()
setSessionDynFlags DynFlags
dflags0 = do
Logger
logger <- forall (m :: * -> *). HasLogger m => m Logger
getLogger
DynFlags
dflags1 <- forall (m :: * -> *). MonadIO m => Logger -> DynFlags -> m DynFlags
checkNewDynFlags Logger
logger DynFlags
dflags0
HscEnv
hsc_env <- forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
let cached_unit_dbs :: Maybe [UnitDatabase UnitId]
cached_unit_dbs = HscEnv -> Maybe [UnitDatabase UnitId]
hsc_unit_dbs HscEnv
hsc_env
([UnitDatabase UnitId]
dbs,UnitState
unit_state,HomeUnit
home_unit,Maybe PlatformConstants
mconstants) <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ Logger
-> DynFlags
-> Maybe [UnitDatabase UnitId]
-> IO
([UnitDatabase UnitId], UnitState, HomeUnit,
Maybe PlatformConstants)
initUnits Logger
logger DynFlags
dflags1 Maybe [UnitDatabase UnitId]
cached_unit_dbs
DynFlags
dflags <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ DynFlags -> Maybe PlatformConstants -> IO DynFlags
updatePlatformConstants DynFlags
dflags1 Maybe PlatformConstants
mconstants
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 forall a. [a] -> [a] -> [a]
++ FilePath
flavour
profiled :: Bool
profiled = DynFlags -> Ways
ways DynFlags
dflags Ways -> Way -> Bool
`hasWay` Way
WayProf
dynamic :: Bool
dynamic = DynFlags -> Ways
ways DynFlags
dflags Ways -> Way -> Bool
`hasWay` Way
WayDyn
flavour :: FilePath
flavour
| Bool
profiled = FilePath
"-prof"
| Bool
dynamic = 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 forall a. Ord a => a -> a -> Bool
>= Int
3
then forall (m :: * -> *) a. Monad m => a -> m a
return (Logger -> DynFlags -> SDoc -> IO ()
logInfo Logger
logger DynFlags
dflags forall a b. (a -> b) -> a -> b
$ PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
defaultDumpStyle SDoc
msg)
else forall (m :: * -> *) a. Monad m => a -> m a
return (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
let
conf :: IServConfig
conf = IServConfig
{ iservConfProgram :: FilePath
iservConfProgram = FilePath
prog
, iservConfOpts :: [FilePath]
iservConfOpts = forall a. DynFlags -> (DynFlags -> [a]) -> [a]
getOpts DynFlags
dflags DynFlags -> [FilePath]
opt_i
, iservConfProfiled :: Bool
iservConfProfiled = Bool
profiled
, iservConfDynamic :: Bool
iservConfDynamic = Bool
dynamic
, iservConfHook :: Maybe (CreateProcess -> IO ProcessHandle)
iservConfHook = Hooks -> Maybe (CreateProcess -> IO ProcessHandle)
createIservProcessHook (HscEnv -> Hooks
hsc_hooks HscEnv
hsc_env)
, iservConfTrace :: IO ()
iservConfTrace = IO ()
tr
}
MVar IServState
s <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. a -> IO (MVar a)
newMVar IServState
IServPending
Loader
loader <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO Loader
Loader.uninitializedLoader
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just (InterpInstance -> Loader -> Interp
Interp (IServConfig -> IServ -> InterpInstance
ExternalInterp IServConfig
conf (MVar IServState -> IServ
IServ MVar IServState
s)) Loader
loader))
else
#if defined(HAVE_INTERNAL_INTERPRETER)
do
Loader
loader <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO Loader
Loader.uninitializedLoader
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just (InterpInstance -> Loader -> Interp
Interp InterpInstance
InternalInterp Loader
loader))
#else
return Nothing
#endif
let unit_env :: UnitEnv
unit_env = UnitEnv
{ ue_platform :: Platform
ue_platform = DynFlags -> Platform
targetPlatform DynFlags
dflags
, ue_namever :: GhcNameVersion
ue_namever = DynFlags -> GhcNameVersion
ghcNameVersion DynFlags
dflags
, ue_home_unit :: HomeUnit
ue_home_unit = HomeUnit
home_unit
, ue_units :: UnitState
ue_units = UnitState
unit_state
}
forall (m :: * -> *). GhcMonad m => (HscEnv -> HscEnv) -> m ()
modifySession 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 forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Interp
interp
, hsc_unit_env :: UnitEnv
hsc_unit_env = UnitEnv
unit_env
, hsc_unit_dbs :: Maybe [UnitDatabase UnitId]
hsc_unit_dbs = forall a. a -> Maybe a
Just [UnitDatabase UnitId]
dbs
}
forall (m :: * -> *). GhcMonad m => m ()
invalidateModSummaryCache
setProgramDynFlags :: GhcMonad m => DynFlags -> m Bool
setProgramDynFlags :: forall (m :: * -> *). GhcMonad m => DynFlags -> m Bool
setProgramDynFlags DynFlags
dflags = forall (m :: * -> *). GhcMonad m => Bool -> DynFlags -> m Bool
setProgramDynFlags_ Bool
True DynFlags
dflags
setProgramDynFlags_ :: GhcMonad m => Bool -> DynFlags -> m Bool
setProgramDynFlags_ :: forall (m :: * -> *). GhcMonad m => Bool -> DynFlags -> m Bool
setProgramDynFlags_ Bool
invalidate_needed DynFlags
dflags = do
Logger
logger <- forall (m :: * -> *). HasLogger m => m Logger
getLogger
DynFlags
dflags0 <- forall (m :: * -> *). MonadIO m => Logger -> DynFlags -> m DynFlags
checkNewDynFlags Logger
logger DynFlags
dflags
DynFlags
dflags_prev <- forall (m :: * -> *). GhcMonad m => m DynFlags
getProgramDynFlags
let changed :: Bool
changed = DynFlags -> DynFlags -> Bool
packageFlagsChanged DynFlags
dflags_prev DynFlags
dflags0
if Bool
changed
then do
HscEnv
hsc_env <- forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
let cached_unit_dbs :: Maybe [UnitDatabase UnitId]
cached_unit_dbs = HscEnv -> Maybe [UnitDatabase UnitId]
hsc_unit_dbs HscEnv
hsc_env
([UnitDatabase UnitId]
dbs,UnitState
unit_state,HomeUnit
home_unit,Maybe PlatformConstants
mconstants) <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ Logger
-> DynFlags
-> Maybe [UnitDatabase UnitId]
-> IO
([UnitDatabase UnitId], UnitState, HomeUnit,
Maybe PlatformConstants)
initUnits Logger
logger DynFlags
dflags0 Maybe [UnitDatabase UnitId]
cached_unit_dbs
DynFlags
dflags1 <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ DynFlags -> Maybe PlatformConstants -> IO DynFlags
updatePlatformConstants DynFlags
dflags0 Maybe PlatformConstants
mconstants
let unit_env :: UnitEnv
unit_env = UnitEnv
{ ue_platform :: Platform
ue_platform = DynFlags -> Platform
targetPlatform DynFlags
dflags1
, ue_namever :: GhcNameVersion
ue_namever = DynFlags -> GhcNameVersion
ghcNameVersion DynFlags
dflags1
, ue_home_unit :: HomeUnit
ue_home_unit = HomeUnit
home_unit
, ue_units :: UnitState
ue_units = UnitState
unit_state
}
forall (m :: * -> *). GhcMonad m => (HscEnv -> HscEnv) -> m ()
modifySession forall a b. (a -> b) -> a -> b
$ \HscEnv
h -> HscEnv
h{ hsc_dflags :: DynFlags
hsc_dflags = DynFlags
dflags1
, hsc_unit_dbs :: Maybe [UnitDatabase UnitId]
hsc_unit_dbs = forall a. a -> Maybe a
Just [UnitDatabase UnitId]
dbs
, hsc_unit_env :: UnitEnv
hsc_unit_env = UnitEnv
unit_env
}
else forall (m :: * -> *). GhcMonad m => (HscEnv -> HscEnv) -> m ()
modifySession forall a b. (a -> b) -> a -> b
$ \HscEnv
h -> HscEnv
h{ hsc_dflags :: DynFlags
hsc_dflags = DynFlags
dflags0 }
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
invalidate_needed forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *). GhcMonad m => m ()
invalidateModSummaryCache
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed
invalidateModSummaryCache :: GhcMonad m => m ()
invalidateModSummaryCache :: forall (m :: * -> *). GhcMonad m => m ()
invalidateModSummaryCache =
forall (m :: * -> *). GhcMonad m => (HscEnv -> HscEnv) -> m ()
modifySession 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 :: forall (m :: * -> *). GhcMonad m => m DynFlags
getProgramDynFlags = forall (m :: * -> *). GhcMonad m => m DynFlags
getSessionDynFlags
setInteractiveDynFlags :: GhcMonad m => DynFlags -> m ()
setInteractiveDynFlags :: forall (m :: * -> *). GhcMonad m => DynFlags -> m ()
setInteractiveDynFlags DynFlags
dflags = do
Logger
logger <- forall (m :: * -> *). HasLogger m => m Logger
getLogger
DynFlags
dflags' <- forall (m :: * -> *). MonadIO m => Logger -> DynFlags -> m DynFlags
checkNewDynFlags Logger
logger DynFlags
dflags
DynFlags
dflags'' <- forall (m :: * -> *). MonadIO m => Logger -> DynFlags -> m DynFlags
checkNewInteractiveDynFlags Logger
logger DynFlags
dflags'
forall (m :: * -> *). GhcMonad m => (HscEnv -> m HscEnv) -> m ()
modifySessionM forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env0 -> do
let ic0 :: InteractiveContext
ic0 = HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env0
HscEnv
plugin_env <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ HscEnv -> IO HscEnv
initializePlugins forall a b. (a -> b) -> a -> b
$ HscEnv -> HscEnv
mkInteractiveHscEnv forall a b. (a -> b) -> a -> b
$
HscEnv
hsc_env0 { hsc_IC :: InteractiveContext
hsc_IC = InteractiveContext
ic0 { ic_dflags :: DynFlags
ic_dflags = DynFlags
dflags'' }}
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ HscEnv
hsc_env0
{ hsc_IC :: InteractiveContext
hsc_IC = InteractiveContext
ic0
{ ic_plugins :: [LoadedPlugin]
ic_plugins = HscEnv -> [LoadedPlugin]
hsc_plugins HscEnv
plugin_env
, ic_dflags :: DynFlags
ic_dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
plugin_env
}
}
getInteractiveDynFlags :: GhcMonad m => m DynFlags
getInteractiveDynFlags :: forall (m :: * -> *). GhcMonad m => m DynFlags
getInteractiveDynFlags = forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession forall a b. (a -> b) -> a -> b
$ \HscEnv
h -> forall (m :: * -> *) a. Monad m => a -> m a
return (InteractiveContext -> DynFlags
ic_dflags (HscEnv -> InteractiveContext
hsc_IC HscEnv
h))
parseDynamicFlags
:: MonadIO m
=> Logger
-> DynFlags
-> [Located String]
-> m (DynFlags, [Located String], [Warn])
parseDynamicFlags :: forall (m :: * -> *).
MonadIO m =>
Logger
-> DynFlags
-> [Located FilePath]
-> m (DynFlags, [Located FilePath], [Warn])
parseDynamicFlags Logger
logger DynFlags
dflags [Located FilePath]
cmdline = do
(DynFlags
dflags1, [Located FilePath]
leftovers, [Warn]
warns) <- forall (m :: * -> *).
MonadIO m =>
DynFlags
-> [Located FilePath] -> m (DynFlags, [Located FilePath], [Warn])
parseDynamicFlagsCmdLine DynFlags
dflags [Located FilePath]
cmdline
DynFlags
dflags2 <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ Logger -> DynFlags -> IO DynFlags
interpretPackageEnv Logger
logger DynFlags
dflags1
forall (m :: * -> *) a. Monad m => a -> m a
return (DynFlags
dflags2, [Located FilePath]
leftovers, [Warn]
warns)
parseTargetFiles :: DynFlags -> [String] -> (DynFlags, [(String, Maybe Phase)], [String])
parseTargetFiles :: DynFlags
-> [FilePath] -> (DynFlags, [(FilePath, Maybe Phase)], [FilePath])
parseTargetFiles DynFlags
dflags0 [FilePath]
fileish_args =
let
normal_fileish_paths :: [FilePath]
normal_fileish_paths = forall a b. (a -> b) -> [a] -> [b]
map FilePath -> FilePath
normalise_hyp [FilePath]
fileish_args
([(FilePath, Maybe Phase)]
srcs, [FilePath]
objs) = [FilePath]
-> [(FilePath, Maybe Phase)]
-> [FilePath]
-> ([(FilePath, Maybe Phase)], [FilePath])
partition_args [FilePath]
normal_fileish_paths [] []
dflags1 :: DynFlags
dflags1 = DynFlags
dflags0 { ldInputs :: [Option]
ldInputs = forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> FilePath -> Option
FileOption FilePath
"") [FilePath]
objs
forall a. [a] -> [a] -> [a]
++ DynFlags -> [Option]
ldInputs DynFlags
dflags0 }
in (DynFlags
dflags1, [(FilePath, Maybe Phase)]
srcs, [FilePath]
objs)
partition_args :: [String] -> [(String, Maybe Phase)] -> [String]
-> ([(String, Maybe Phase)], [String])
partition_args :: [FilePath]
-> [(FilePath, Maybe Phase)]
-> [FilePath]
-> ([(FilePath, Maybe Phase)], [FilePath])
partition_args [] [(FilePath, Maybe Phase)]
srcs [FilePath]
objs = (forall a. [a] -> [a]
reverse [(FilePath, Maybe Phase)]
srcs, forall a. [a] -> [a]
reverse [FilePath]
objs)
partition_args (FilePath
"-x":FilePath
suff:[FilePath]
args) [(FilePath, Maybe Phase)]
srcs [FilePath]
objs
| FilePath
"none" <- FilePath
suff = [FilePath]
-> [(FilePath, Maybe Phase)]
-> [FilePath]
-> ([(FilePath, Maybe Phase)], [FilePath])
partition_args [FilePath]
args [(FilePath, Maybe Phase)]
srcs [FilePath]
objs
| Phase
StopLn <- Phase
phase = [FilePath]
-> [(FilePath, Maybe Phase)]
-> [FilePath]
-> ([(FilePath, Maybe Phase)], [FilePath])
partition_args [FilePath]
args [(FilePath, Maybe Phase)]
srcs ([FilePath]
slurp forall a. [a] -> [a] -> [a]
++ [FilePath]
objs)
| Bool
otherwise = [FilePath]
-> [(FilePath, Maybe Phase)]
-> [FilePath]
-> ([(FilePath, Maybe Phase)], [FilePath])
partition_args [FilePath]
rest ([(FilePath, Maybe Phase)]
these_srcs forall a. [a] -> [a] -> [a]
++ [(FilePath, Maybe Phase)]
srcs) [FilePath]
objs
where phase :: Phase
phase = FilePath -> Phase
startPhase FilePath
suff
([FilePath]
slurp,[FilePath]
rest) = forall a. (a -> Bool) -> [a] -> ([a], [a])
break (forall a. Eq a => a -> a -> Bool
== FilePath
"-x") [FilePath]
args
these_srcs :: [(FilePath, Maybe Phase)]
these_srcs = forall a b. [a] -> [b] -> [(a, b)]
zip [FilePath]
slurp (forall a. a -> [a]
repeat (forall a. a -> Maybe a
Just Phase
phase))
partition_args (FilePath
arg:[FilePath]
args) [(FilePath, Maybe Phase)]
srcs [FilePath]
objs
| FilePath -> Bool
looks_like_an_input FilePath
arg = [FilePath]
-> [(FilePath, Maybe Phase)]
-> [FilePath]
-> ([(FilePath, Maybe Phase)], [FilePath])
partition_args [FilePath]
args ((FilePath
arg,forall a. Maybe a
Nothing)forall a. a -> [a] -> [a]
:[(FilePath, Maybe Phase)]
srcs) [FilePath]
objs
| Bool
otherwise = [FilePath]
-> [(FilePath, Maybe Phase)]
-> [FilePath]
-> ([(FilePath, Maybe Phase)], [FilePath])
partition_args [FilePath]
args [(FilePath, Maybe Phase)]
srcs (FilePath
argforall a. a -> [a] -> [a]
:[FilePath]
objs)
looks_like_an_input :: String -> Bool
looks_like_an_input :: FilePath -> Bool
looks_like_an_input FilePath
m = FilePath -> Bool
isSourceFilename FilePath
m
Bool -> Bool -> Bool
|| FilePath -> Bool
looksLikeModuleName FilePath
m
Bool -> Bool -> Bool
|| FilePath
"-" forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` FilePath
m
Bool -> Bool -> Bool
|| Bool -> Bool
not (FilePath -> Bool
hasExtension FilePath
m)
normalise_hyp :: FilePath -> FilePath
normalise_hyp :: FilePath -> FilePath
normalise_hyp FilePath
fp
| Bool
strt_dot_sl Bool -> Bool -> Bool
&& FilePath
"-" forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` FilePath
nfp = FilePath
cur_dir forall a. [a] -> [a] -> [a]
++ FilePath
nfp
| Bool
otherwise = FilePath
nfp
where
#if defined(mingw32_HOST_OS)
strt_dot_sl = "./" `isPrefixOf` fp || ".\\" `isPrefixOf` fp
#else
strt_dot_sl :: Bool
strt_dot_sl = FilePath
"./" forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` FilePath
fp
#endif
cur_dir :: FilePath
cur_dir = Char
'.' forall a. a -> [a] -> [a]
: [Char
pathSeparator]
nfp :: FilePath
nfp = FilePath -> FilePath
normalise FilePath
fp
checkNewDynFlags :: MonadIO m => Logger -> DynFlags -> m DynFlags
checkNewDynFlags :: forall (m :: * -> *). MonadIO m => Logger -> DynFlags -> m DynFlags
checkNewDynFlags Logger
logger DynFlags
dflags = do
let (DynFlags
dflags', [Located FilePath]
warnings) = DynFlags -> (DynFlags, [Located FilePath])
makeDynFlagsConsistent DynFlags
dflags
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ Logger -> DynFlags -> [Warn] -> IO ()
handleFlagWarnings Logger
logger DynFlags
dflags (forall a b. (a -> b) -> [a] -> [b]
map (WarnReason -> Located FilePath -> Warn
Warn WarnReason
NoReason) [Located FilePath]
warnings)
forall (m :: * -> *) a. Monad m => a -> m a
return DynFlags
dflags'
checkNewInteractiveDynFlags :: MonadIO m => Logger -> DynFlags -> m DynFlags
checkNewInteractiveDynFlags :: forall (m :: * -> *). MonadIO m => Logger -> DynFlags -> m DynFlags
checkNewInteractiveDynFlags Logger
logger DynFlags
dflags0 = do
if Extension -> DynFlags -> Bool
xopt Extension
LangExt.StaticPointers DynFlags
dflags0
then do forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ Logger -> DynFlags -> Bag WarnMsg -> IO ()
printOrThrowWarnings Logger
logger DynFlags
dflags0 forall a b. (a -> b) -> a -> b
$ forall a. [a] -> Bag a
listToBag
[SrcSpan -> SDoc -> WarnMsg
mkPlainWarnMsg SrcSpan
interactiveSrcSpan
forall a b. (a -> b) -> a -> b
$ FilePath -> SDoc
text FilePath
"StaticPointers is not supported in GHCi interactive expressions."]
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ DynFlags -> Extension -> DynFlags
xopt_unset DynFlags
dflags0 Extension
LangExt.StaticPointers
else forall (m :: * -> *) a. Monad m => a -> m a
return DynFlags
dflags0
setTargets :: GhcMonad m => [Target] -> m ()
setTargets :: forall (m :: * -> *). GhcMonad m => [Target] -> m ()
setTargets [Target]
targets = forall (m :: * -> *). GhcMonad m => (HscEnv -> HscEnv) -> m ()
modifySession (\HscEnv
h -> HscEnv
h{ hsc_targets :: [Target]
hsc_targets = [Target]
targets })
getTargets :: GhcMonad m => m [Target]
getTargets :: forall (m :: * -> *). GhcMonad m => m [Target]
getTargets = forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession (forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. HscEnv -> [Target]
hsc_targets)
addTarget :: GhcMonad m => Target -> m ()
addTarget :: forall (m :: * -> *). GhcMonad m => Target -> m ()
addTarget Target
target
= forall (m :: * -> *). GhcMonad m => (HscEnv -> HscEnv) -> m ()
modifySession (\HscEnv
h -> HscEnv
h{ hsc_targets :: [Target]
hsc_targets = Target
target forall a. a -> [a] -> [a]
: HscEnv -> [Target]
hsc_targets HscEnv
h })
removeTarget :: GhcMonad m => TargetId -> m ()
removeTarget :: forall (m :: * -> *). GhcMonad m => TargetId -> m ()
removeTarget TargetId
target_id
= forall (m :: * -> *). GhcMonad m => (HscEnv -> HscEnv) -> 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 forall a. Eq a => a -> a -> Bool
/= TargetId
target_id ]
guessTarget :: GhcMonad m => String -> Maybe Phase -> m Target
guessTarget :: forall (m :: * -> *).
GhcMonad m =>
FilePath -> Maybe Phase -> m Target
guessTarget FilePath
str (Just Phase
phase)
= forall (m :: * -> *) a. Monad m => a -> m a
return (TargetId -> Bool -> Maybe (InputFileBuffer, UTCTime) -> Target
Target (FilePath -> Maybe Phase -> TargetId
TargetFile FilePath
str (forall a. a -> Maybe a
Just Phase
phase)) Bool
True forall a. Maybe a
Nothing)
guessTarget FilePath
str Maybe Phase
Nothing
| FilePath -> Bool
isHaskellSrcFilename FilePath
file
= forall (m :: * -> *) a. Monad m => a -> m a
return (TargetId -> Target
target (FilePath -> Maybe Phase -> TargetId
TargetFile FilePath
file forall a. Maybe a
Nothing))
| Bool
otherwise
= do Bool
exists <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
doesFileExist FilePath
hs_file
if Bool
exists
then forall (m :: * -> *) a. Monad m => a -> m a
return (TargetId -> Target
target (FilePath -> Maybe Phase -> TargetId
TargetFile FilePath
hs_file forall a. Maybe a
Nothing))
else do
Bool
exists <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
doesFileExist FilePath
lhs_file
if Bool
exists
then forall (m :: * -> *) a. Monad m => a -> m a
return (TargetId -> Target
target (FilePath -> Maybe Phase -> TargetId
TargetFile FilePath
lhs_file forall a. Maybe a
Nothing))
else do
if FilePath -> Bool
looksLikeModuleName FilePath
file
then forall (m :: * -> *) a. Monad m => a -> m a
return (TargetId -> Target
target (ModuleName -> TargetId
TargetModule (FilePath -> ModuleName
mkModuleName FilePath
file)))
else do
DynFlags
dflags <- forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. GhcException -> IO a
throwGhcExceptionIO
(FilePath -> GhcException
ProgramError (DynFlags -> SDoc -> FilePath
showSDoc DynFlags
dflags 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 forall a. Maybe a
Nothing
workingDirectoryChanged :: GhcMonad m => m ()
workingDirectoryChanged :: forall (m :: * -> *). GhcMonad m => m ()
workingDirectoryChanged = forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession forall a b. (a -> b) -> a -> b
$ (forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO 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] }
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 = forall m. ParsedMod m => m -> ModSummary
modSummary (TypecheckedModule -> ParsedModule
tm_parsed_module TypecheckedModule
m)
parsedSource :: TypecheckedModule -> ParsedSource
parsedSource TypecheckedModule
m = forall m. ParsedMod m => m -> ParsedSource
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 = forall m. ParsedMod m => m -> ModSummary
modSummary (DesugaredModule -> TypecheckedModule
dm_typechecked_module DesugaredModule
m)
parsedSource :: DesugaredModule -> ParsedSource
parsedSource DesugaredModule
m = forall m. ParsedMod m => m -> ParsedSource
parsedSource (DesugaredModule -> TypecheckedModule
dm_typechecked_module DesugaredModule
m)
instance TypecheckedMod DesugaredModule where
renamedSource :: DesugaredModule -> Maybe RenamedSource
renamedSource DesugaredModule
m = forall m. TypecheckedMod m => m -> Maybe RenamedSource
renamedSource (DesugaredModule -> TypecheckedModule
dm_typechecked_module DesugaredModule
m)
typecheckedSource :: DesugaredModule -> TypecheckedSource
typecheckedSource DesugaredModule
m = forall m. TypecheckedMod m => m -> TypecheckedSource
typecheckedSource (DesugaredModule -> TypecheckedModule
dm_typechecked_module DesugaredModule
m)
moduleInfo :: DesugaredModule -> ModuleInfo
moduleInfo DesugaredModule
m = forall m. TypecheckedMod m => m -> ModuleInfo
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 :: forall (m :: * -> *). GhcMonad m => ModuleName -> m ModSummary
getModSummary ModuleName
mod = do
ModuleGraph
mg <- forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM HscEnv -> ModuleGraph
hsc_mod_graph forall (m :: * -> *). GhcMonad m => m HscEnv
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 forall a. Eq a => a -> a -> Bool
== ModuleName
mod
, ModSummary -> IsBootInterface
isBootSummary ModSummary
ms forall a. Eq a => a -> a -> Bool
== IsBootInterface
NotBoot ]
case [ModSummary]
mods_by_name of
[] -> do DynFlags
dflags <- forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => e -> IO a
throwIO 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] -> forall (m :: * -> *) a. Monad m => a -> m a
return ModSummary
ms
[ModSummary]
multiple -> do DynFlags
dflags <- forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ DynFlags -> SDoc -> GhcApiError
mkApiErr DynFlags
dflags (FilePath -> SDoc
text FilePath
"getModSummary is ambiguous: " SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr [ModSummary]
multiple)
parseModule :: GhcMonad m => ModSummary -> m ParsedModule
parseModule :: forall (m :: * -> *). GhcMonad m => ModSummary -> m ParsedModule
parseModule ModSummary
ms = do
HscEnv
hsc_env <- forall (m :: * -> *). GhcMonad m => m HscEnv
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 <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ HscEnv -> ModSummary -> IO HsParsedModule
hscParse HscEnv
hsc_env_tmp ModSummary
ms
forall (m :: * -> *) a. Monad m => a -> m a
return (ModSummary -> ParsedSource -> [FilePath] -> ParsedModule
ParsedModule ModSummary
ms (HsParsedModule -> ParsedSource
hpm_module HsParsedModule
hpm) (HsParsedModule -> [FilePath]
hpm_src_files HsParsedModule
hpm))
typecheckModule :: GhcMonad m => ParsedModule -> m TypecheckedModule
typecheckModule :: forall (m :: * -> *).
GhcMonad m =>
ParsedModule -> m TypecheckedModule
typecheckModule ParsedModule
pmod = do
let ms :: ModSummary
ms = forall m. ParsedMod m => m -> ModSummary
modSummary ParsedModule
pmod
HscEnv
hsc_env <- forall (m :: * -> *). GhcMonad m => m HscEnv
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
(HsGroup GhcRn, [GenLocated SrcSpanAnnA (ImportDecl GhcRn)],
Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), Avails)],
Maybe LHsDocString)
rn_info)
<- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ HscEnv
-> ModSummary
-> HsParsedModule
-> IO (TcGblEnv, Maybe RenamedSource)
hscTypecheckRename HscEnv
hsc_env_tmp ModSummary
ms forall a b. (a -> b) -> a -> b
$
HsParsedModule { hpm_module :: ParsedSource
hpm_module = forall m. ParsedMod m => m -> ParsedSource
parsedSource ParsedModule
pmod,
hpm_src_files :: [FilePath]
hpm_src_files = ParsedModule -> [FilePath]
pm_extra_src_files ParsedModule
pmod }
ModDetails
details <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ HscEnv -> TcGblEnv -> IO ModDetails
makeSimpleDetails HscEnv
hsc_env_tmp TcGblEnv
tc_gbl_env
SafeHaskellMode
safe <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ DynFlags -> TcGblEnv -> IO SafeHaskellMode
finalSafeMode (ModSummary -> DynFlags
ms_hspp_opts ModSummary
ms) TcGblEnv
tc_gbl_env
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
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
(HsGroup GhcRn, [GenLocated SrcSpanAnnA (ImportDecl GhcRn)],
Maybe [(GenLocated SrcSpanAnnA (IE GhcRn), Avails)],
Maybe LHsDocString)
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 {
minf_type_env :: TypeEnv
minf_type_env = ModDetails -> TypeEnv
md_types ModDetails
details,
minf_exports :: Avails
minf_exports = ModDetails -> Avails
md_exports ModDetails
details,
minf_rdr_env :: Maybe GlobalRdrEnv
minf_rdr_env = 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 forall a b. (a -> b) -> a -> b
$ ModDetails -> [ClsInst]
md_insts ModDetails
details,
minf_iface :: Maybe ModIface
minf_iface = 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 :: forall (m :: * -> *).
GhcMonad m =>
TypecheckedModule -> m DesugaredModule
desugarModule TypecheckedModule
tcm = do
let ms :: ModSummary
ms = forall m. ParsedMod m => m -> ModSummary
modSummary TypecheckedModule
tcm
let (TcGblEnv
tcg, ModDetails
_) = forall m. TypecheckedMod m => m -> (TcGblEnv, ModDetails)
tm_internals TypecheckedModule
tcm
HscEnv
hsc_env <- forall (m :: * -> *). GhcMonad m => m HscEnv
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 <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ HscEnv -> ModSummary -> TcGblEnv -> IO ModGuts
hscDesugar HscEnv
hsc_env_tmp ModSummary
ms TcGblEnv
tcg
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
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 :: forall mod (m :: * -> *).
(TypecheckedMod mod, GhcMonad m) =>
mod -> m mod
loadModule mod
tcm = do
let ms :: ModSummary
ms = forall m. ParsedMod m => m -> ModSummary
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) = forall m. TypecheckedMod m => m -> (TcGblEnv, ModDetails)
tm_internals mod
tcm
Maybe Linkable
mb_linkable <- case ModSummary -> Maybe UTCTime
ms_obj_date ModSummary
ms of
Just UTCTime
t | UTCTime
t forall a. Ord a => a -> a -> Bool
> ModSummary -> UTCTime
ms_hs_date ModSummary
ms -> do
Linkable
l <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO 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
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just Linkable
l)
Maybe UTCTime
_otherwise -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
let source_modified :: SourceModified
source_modified | forall a. Maybe a -> Bool
isNothing Maybe Linkable
mb_linkable = SourceModified
SourceModified
| Bool
otherwise = SourceModified
SourceUnmodified
HscEnv
hsc_env <- forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
HomeModInfo
mod_info <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ Maybe TcGblEnv
-> Maybe Messager
-> HscEnv
-> ModSummary
-> Int
-> Int
-> Maybe ModIface
-> Maybe Linkable
-> SourceModified
-> IO HomeModInfo
compileOne' (forall a. a -> Maybe a
Just TcGblEnv
tcg) forall a. Maybe a
Nothing
HscEnv
hsc_env ModSummary
ms Int
1 Int
1 forall a. Maybe a
Nothing Maybe Linkable
mb_linkable
SourceModified
source_modified
forall (m :: * -> *). GhcMonad m => (HscEnv -> HscEnv) -> m ()
modifySession 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 }
forall (m :: * -> *) a. Monad m => a -> m a
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
<+> forall a. Outputable a => a -> SDoc
ppr Module
mn SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
parens (forall a. Outputable a => a -> SDoc
ppr SafeHaskellMode
sf) SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr TypeEnv
te
SDoc -> SDoc -> SDoc
$$ [SDoc] -> SDoc
vcat (forall a b. (a -> b) -> [a] -> [b]
map forall a. Outputable a => a -> SDoc
ppr CoreProgram
cb)
compileToCoreModule :: GhcMonad m => FilePath -> m CoreModule
compileToCoreModule :: forall (m :: * -> *). GhcMonad m => FilePath -> m CoreModule
compileToCoreModule = forall (m :: * -> *).
GhcMonad m =>
Bool -> FilePath -> m CoreModule
compileCore Bool
False
compileToCoreSimplified :: GhcMonad m => FilePath -> m CoreModule
compileToCoreSimplified :: forall (m :: * -> *). GhcMonad m => FilePath -> m CoreModule
compileToCoreSimplified = forall (m :: * -> *).
GhcMonad m =>
Bool -> FilePath -> m CoreModule
compileCore Bool
True
compileCore :: GhcMonad m => Bool -> FilePath -> m CoreModule
compileCore :: forall (m :: * -> *).
GhcMonad m =>
Bool -> FilePath -> m CoreModule
compileCore Bool
simplify FilePath
fn = do
Target
target <- forall (m :: * -> *).
GhcMonad m =>
FilePath -> Maybe Phase -> m Target
guessTarget FilePath
fn forall a. Maybe a
Nothing
forall (m :: * -> *). GhcMonad m => Target -> m ()
addTarget Target
target
SuccessFlag
_ <- forall (m :: * -> *). GhcMonad m => LoadHowMuch -> m SuccessFlag
load LoadHowMuch
LoadAllTargets
ModuleGraph
modGraph <- forall (m :: * -> *).
GhcMonad m =>
[ModuleName] -> Bool -> m ModuleGraph
depanal [] Bool
True
case forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find ((forall a. Eq a => a -> a -> Bool
== FilePath
fn) 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 <- forall (m :: * -> *).
GhcMonad m =>
ParsedModule -> m TypecheckedModule
typecheckModule forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall (m :: * -> *). GhcMonad m => ModSummary -> m ParsedModule
parseModule ModSummary
modSummary
let tcg :: TcGblEnv
tcg = forall a b. (a, b) -> a
fst (forall m. TypecheckedMod m => m -> (TcGblEnv, ModDetails)
tm_internals TypecheckedModule
tm)
(,) TcGblEnv
tcg forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall m. DesugaredMod m => m -> ModGuts
coreModule forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *).
GhcMonad m =>
TypecheckedModule -> m DesugaredModule
desugarModule TypecheckedModule
tm
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (SafeHaskellMode
-> Either (CgGuts, ModDetails) ModGuts -> CoreModule
gutsToCoreModule (ModGuts -> SafeHaskellMode
mg_safe_haskell ModGuts
mod_guts)) forall a b. (a -> b) -> a -> b
$
if Bool
simplify
then do
HscEnv
hsc_env <- forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
ModGuts
simpl_guts <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
[FilePath]
plugins <- forall a. IORef a -> IO a
readIORef (TcGblEnv -> TcRef [FilePath]
tcg_th_coreplugins TcGblEnv
tcg)
HscEnv -> [FilePath] -> ModGuts -> IO ModGuts
hscSimplify HscEnv
hsc_env [FilePath]
plugins ModGuts
mod_guts
(CgGuts, ModDetails)
tidy_guts <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ HscEnv -> ModGuts -> IO (CgGuts, ModDetails)
tidyProgram HscEnv
hsc_env ModGuts
simpl_guts
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left (CgGuts, ModDetails)
tidy_guts
else
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right ModGuts
mod_guts
Maybe ModSummary
Nothing -> 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 {
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 {
cm_module :: Module
cm_module = ModGuts -> Module
mg_module ModGuts
mg,
cm_types :: TypeEnv
cm_types = [Var] -> [TyCon] -> [PatSyn] -> [FamInst] -> TypeEnv
typeEnvFromEntities (forall b. [Bind b] -> [b]
bindersOfBinds (ModGuts -> CoreProgram
mg_binds ModGuts
mg))
(ModGuts -> [TyCon]
mg_tcs ModGuts
mg) (ModGuts -> [PatSyn]
mg_patsyns 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 :: forall (m :: * -> *). GhcMonad m => m ModuleGraph
getModuleGraph = forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM HscEnv -> ModuleGraph
hsc_mod_graph forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
isLoaded :: GhcMonad m => ModuleName -> m Bool
isLoaded :: forall (m :: * -> *). GhcMonad m => ModuleName -> m Bool
isLoaded ModuleName
m = forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env ->
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! 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 :: forall (m :: * -> *). GhcMonad m => m [TyThing]
getBindings = forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env ->
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ InteractiveContext -> [TyThing]
icInScopeTTs forall a b. (a -> b) -> a -> b
$ HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env
getInsts :: GhcMonad m => m ([ClsInst], [FamInst])
getInsts :: forall (m :: * -> *). GhcMonad m => m ([ClsInst], [FamInst])
getInsts = forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env ->
forall (m :: * -> *) a. Monad m => a -> m a
return 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 :: forall (m :: * -> *). GhcMonad m => m PrintUnqualified
getPrintUnqual = forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> do
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ UnitEnv -> InteractiveContext -> PrintUnqualified
icPrintUnqual (HscEnv -> UnitEnv
hsc_unit_env HscEnv
hsc_env) (HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env)
data ModuleInfo = ModuleInfo {
ModuleInfo -> TypeEnv
minf_type_env :: TypeEnv,
ModuleInfo -> Avails
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 :: forall (m :: * -> *). GhcMonad m => Module -> m (Maybe ModuleInfo)
getModuleInfo Module
mdl = forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession 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 forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ HscEnv -> Module -> IO (Maybe ModuleInfo)
getHomeModuleInfo HscEnv
hsc_env Module
mdl
else do
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO 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 :: Avails
avails = forall (phase :: ModIfacePhase). ModIface_ phase -> Avails
mi_exports ModIface
iface
pte :: TypeEnv
pte = ExternalPackageState -> TypeEnv
eps_PTE ExternalPackageState
eps
tys :: [TyThing]
tys = [ TyThing
ty | Name
name <- forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap AvailInfo -> [Name]
availNames Avails
avails,
Just TyThing
ty <- [TypeEnv -> Name -> Maybe TyThing
lookupTypeEnv TypeEnv
pte Name
name] ]
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just (ModuleInfo {
minf_type_env :: TypeEnv
minf_type_env = [TyThing] -> TypeEnv
mkTypeEnv [TyThing]
tys,
minf_exports :: Avails
minf_exports = Avails
avails,
minf_rdr_env :: Maybe GlobalRdrEnv
minf_rdr_env = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$! ModuleName -> Avails -> GlobalRdrEnv
availsToGlobalRdrEnv (forall unit. GenModule unit -> ModuleName
moduleName Module
mdl) Avails
avails,
minf_instances :: [ClsInst]
minf_instances = forall a. HasCallStack => FilePath -> a
error FilePath
"getModuleInfo: instances for package module unimplemented",
minf_iface :: Maybe ModIface
minf_iface = forall a. a -> Maybe a
Just ModIface
iface,
minf_safe :: SafeHaskellMode
minf_safe = IfaceTrustInfo -> SafeHaskellMode
getSafeMode forall a b. (a -> b) -> a -> b
$ forall (phase :: ModIfacePhase). ModIface_ phase -> IfaceTrustInfo
mi_trust ModIface
iface,
minf_modBreaks :: ModBreaks
minf_modBreaks = ModBreaks
emptyModBreaks
}))
availsToGlobalRdrEnv :: ModuleName -> [AvailInfo] -> GlobalRdrEnv
availsToGlobalRdrEnv :: ModuleName -> Avails -> GlobalRdrEnv
availsToGlobalRdrEnv ModuleName
mod_name Avails
avails
= [GlobalRdrElt] -> GlobalRdrEnv
mkGlobalRdrEnv (Maybe ImportSpec -> Avails -> [GlobalRdrElt]
gresFromAvails (forall a. a -> Maybe a
Just ImportSpec
imp_spec) Avails
avails)
where
imp_spec :: ImportSpec
imp_spec = ImpSpec { is_decl :: ImpDeclSpec
is_decl = ImpDeclSpec
decl, is_item :: ImpItemSpec
is_item = ImpItemSpec
ImpAll}
decl :: ImpDeclSpec
decl = ImpDeclSpec { is_mod :: ModuleName
is_mod = ModuleName
mod_name, is_as :: ModuleName
is_as = ModuleName
mod_name,
is_qual :: Bool
is_qual = Bool
False,
is_dloc :: SrcSpan
is_dloc = SrcLoc -> SrcSpan
srcLocSpan SrcLoc
interactiveSrcLoc }
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) (forall unit. GenModule unit -> ModuleName
moduleName Module
mdl) of
Maybe HomeModInfo
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return 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
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just (ModuleInfo {
minf_type_env :: TypeEnv
minf_type_env = ModDetails -> TypeEnv
md_types ModDetails
details,
minf_exports :: Avails
minf_exports = ModDetails -> Avails
md_exports ModDetails
details,
minf_rdr_env :: Maybe GlobalRdrEnv
minf_rdr_env = forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe GlobalRdrEnv
mi_globals 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 = forall a. a -> Maybe a
Just ModIface
iface,
minf_safe :: SafeHaskellMode
minf_safe = IfaceTrustInfo -> SafeHaskellMode
getSafeMode forall a b. (a -> b) -> a -> b
$ 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
= forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a b. (a -> b) -> [a] -> [b]
map GlobalRdrElt -> Name
greMangledName 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 = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap AvailInfo -> [Name]
availNames forall a b. (a -> b) -> a -> b
$! ModuleInfo -> Avails
minf_exports ModuleInfo
minf
modInfoExportsWithSelectors :: ModuleInfo -> [Name]
modInfoExportsWithSelectors :: ModuleInfo -> [Name]
modInfoExportsWithSelectors ModuleInfo
minf = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap AvailInfo -> [Name]
availNamesWithSelectors forall a b. (a -> b) -> a -> b
$! ModuleInfo -> Avails
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 (Avails -> NameSet
availsToNameSet (ModuleInfo -> Avails
minf_exports ModuleInfo
minf))
mkPrintUnqualifiedForModule :: GhcMonad m =>
ModuleInfo
-> m (Maybe PrintUnqualified)
mkPrintUnqualifiedForModule :: forall (m :: * -> *).
GhcMonad m =>
ModuleInfo -> m (Maybe PrintUnqualified)
mkPrintUnqualifiedForModule ModuleInfo
minf = forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> do
let mk_print_unqual :: GlobalRdrEnv -> PrintUnqualified
mk_print_unqual = UnitEnv -> GlobalRdrEnv -> PrintUnqualified
mkPrintUnqualified (HscEnv -> UnitEnv
hsc_unit_env HscEnv
hsc_env)
forall (m :: * -> *) a. Monad m => a -> m a
return (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap GlobalRdrEnv -> PrintUnqualified
mk_print_unqual (ModuleInfo -> Maybe GlobalRdrEnv
minf_rdr_env ModuleInfo
minf))
modInfoLookupName :: GhcMonad m =>
ModuleInfo -> Name
-> m (Maybe TyThing)
modInfoLookupName :: forall (m :: * -> *).
GhcMonad m =>
ModuleInfo -> Name -> m (Maybe TyThing)
modInfoLookupName ModuleInfo
minf Name
name = forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession 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 -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just TyThing
tyThing)
Maybe TyThing
Nothing -> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (HscEnv -> Name -> IO (Maybe TyThing)
lookupType HscEnv
hsc_env 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 :: forall (m :: * -> *). GhcMonad m => Name -> m (Maybe TyThing)
lookupGlobalName Name
name = forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> do
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ HscEnv -> Name -> IO (Maybe TyThing)
lookupType HscEnv
hsc_env Name
name
findGlobalAnns :: (GhcMonad m, Typeable a) => ([Word8] -> a) -> AnnTarget Name -> m [a]
findGlobalAnns :: forall (m :: * -> *) a.
(GhcMonad m, Typeable a) =>
([Word8] -> a) -> AnnTarget Name -> m [a]
findGlobalAnns [Word8] -> a
deserialize AnnTarget Name
target = forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> do
AnnEnv
ann_env <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ HscEnv -> Maybe ModGuts -> IO AnnEnv
prepareAnnotations HscEnv
hsc_env forall a. Maybe a
Nothing
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a.
Typeable a =>
([Word8] -> a) -> AnnEnv -> AnnTarget Name -> [a]
findAnns [Word8] -> a
deserialize AnnEnv
ann_env AnnTarget Name
target)
getGRE :: GhcMonad m => m GlobalRdrEnv
getGRE :: forall (m :: * -> *). GhcMonad m => m GlobalRdrEnv
getGRE = forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env-> forall (m :: * -> *) a. Monad m => a -> m a
return 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 DecoratedSDoc, Maybe (NameEnv ([ClsInst], [FamInst])))
getNameToInstancesIndex :: forall (m :: * -> *).
GhcMonad m =>
[Module]
-> Maybe [Module]
-> m (Messages DecoratedSDoc,
Maybe (NameEnv ([ClsInst], [FamInst])))
getNameToInstancesIndex [Module]
visible_mods Maybe [Module]
mods_to_load = do
HscEnv
hsc_env <- forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. HscEnv -> TcRn a -> IO (Messages DecoratedSDoc, Maybe a)
runTcInteractive HscEnv
hsc_env 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 forall a. IfG a -> TcRn a
initIfaceTcRn forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (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 = forall k a. Ord k => (a -> a -> a) -> [(k, a)] -> Map k a
Map.fromListWith forall a. Monoid a => a -> a -> a
mappend
[ (Name
n, forall a. a -> Seq a
Seq.singleton ClsInst
ispec)
| ClsInst
ispec <- InstEnv -> [ClsInst]
instEnvElts InstEnv
ie_local 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 forall a b. (a -> b) -> a -> b
$ ClsInst -> NameSet
orphNamesOfClsInst ClsInst
ispec
]
; let fam_index :: Map Name (Seq FamInst)
fam_index = forall k a. Ord k => (a -> a -> a) -> [(k, a)] -> Map k a
Map.fromListWith forall a. Monoid a => a -> a -> a
mappend
[ (Name
n, forall a. a -> Seq a
Seq.singleton FamInst
fispec)
| FamInst
fispec <- FamInstEnv -> [FamInst]
famInstEnvElts FamInstEnv
home_fie forall a. [a] -> [a] -> [a]
++ FamInstEnv -> [FamInst]
famInstEnvElts FamInstEnv
pkg_fie
, Name
n <- NameSet -> [Name]
nameSetElemsStable forall a b. (a -> b) -> a -> b
$ FamInst -> NameSet
orphNamesOfFamInst FamInst
fispec
]
; forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. [(Name, a)] -> NameEnv a
mkNameEnv forall a b. (a -> b) -> a -> b
$
[ (Name
nm, (forall (t :: * -> *) a. Foldable t => t a -> [a]
toList Seq ClsInst
clss, forall (t :: * -> *) a. Foldable t => t a -> [a]
toList Seq FamInst
fams))
| (Name
nm, (Seq ClsInst
clss, Seq FamInst
fams)) <- forall k a. Map k a -> [(k, a)]
Map.toList forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
Map.unionWith forall a. Monoid a => a -> a -> a
mappend
(forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (,forall a. Seq a
Seq.empty) Map Name (Seq ClsInst)
cls_index)
(forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (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 :: forall a. NamedThing a => a -> SDoc
pprParenSymName a
a = OccName -> SDoc -> SDoc
parenSymOcc (forall a. NamedThing a => a -> OccName
getOccName a
a) (forall a. Outputable a => a -> SDoc
ppr (forall a. NamedThing a => a -> Name
getName a
a))
getModuleSourceAndFlags :: GhcMonad m => Module -> m (String, StringBuffer, DynFlags)
getModuleSourceAndFlags :: forall (m :: * -> *).
GhcMonad m =>
Module -> m (FilePath, InputFileBuffer, DynFlags)
getModuleSourceAndFlags Module
mod = do
ModSummary
m <- forall (m :: * -> *). GhcMonad m => ModuleName -> m ModSummary
getModSummary (forall unit. GenModule unit -> ModuleName
moduleName Module
mod)
case ModLocation -> Maybe FilePath
ml_hs_file forall a b. (a -> b) -> a -> b
$ ModSummary -> ModLocation
ms_location ModSummary
m of
Maybe FilePath
Nothing -> do DynFlags
dflags <- forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => e -> IO a
throwIO 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
<+> forall a. Outputable a => a -> SDoc
ppr Module
mod)
Just FilePath
sourceFile -> do
InputFileBuffer
source <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO InputFileBuffer
hGetStringBuffer FilePath
sourceFile
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath
sourceFile, InputFileBuffer
source, ModSummary -> DynFlags
ms_hspp_opts ModSummary
m)
getTokenStream :: GhcMonad m => Module -> m [Located Token]
getTokenStream :: forall (m :: * -> *). GhcMonad m => Module -> m [Located Token]
getTokenStream Module
mod = do
(FilePath
sourceFile, InputFileBuffer
source, DynFlags
dflags) <- forall (m :: * -> *).
GhcMonad m =>
Module -> m (FilePath, InputFileBuffer, DynFlags)
getModuleSourceAndFlags Module
mod
let startLoc :: RealSrcLoc
startLoc = FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc (FilePath -> FastString
mkFastString FilePath
sourceFile) Int
1 Int
1
case ParserOpts
-> InputFileBuffer -> RealSrcLoc -> ParseResult [Located Token]
lexTokenStream (DynFlags -> ParserOpts
initParserOpts DynFlags
dflags) InputFileBuffer
source RealSrcLoc
startLoc of
POk PState
_ [Located Token]
ts -> forall (m :: * -> *) a. Monad m => a -> m a
return [Located Token]
ts
PFailed PState
pst -> forall (io :: * -> *) a. MonadIO io => Bag WarnMsg -> io a
throwErrors (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PsError -> WarnMsg
pprError (PState -> Bag PsError
getErrorMessages PState
pst))
getRichTokenStream :: GhcMonad m => Module -> m [(Located Token, String)]
getRichTokenStream :: forall (m :: * -> *).
GhcMonad m =>
Module -> m [(Located Token, FilePath)]
getRichTokenStream Module
mod = do
(FilePath
sourceFile, InputFileBuffer
source, DynFlags
dflags) <- forall (m :: * -> *).
GhcMonad m =>
Module -> m (FilePath, InputFileBuffer, DynFlags)
getModuleSourceAndFlags Module
mod
let startLoc :: RealSrcLoc
startLoc = FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc (FilePath -> FastString
mkFastString FilePath
sourceFile) Int
1 Int
1
case ParserOpts
-> InputFileBuffer -> RealSrcLoc -> ParseResult [Located Token]
lexTokenStream (DynFlags -> ParserOpts
initParserOpts DynFlags
dflags) InputFileBuffer
source RealSrcLoc
startLoc of
POk PState
_ [Located Token]
ts -> forall (m :: * -> *) a. Monad m => a -> m a
return 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 -> forall (io :: * -> *) a. MonadIO io => Bag WarnMsg -> io a
throwErrors (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PsError -> WarnMsg
pprError (PState -> Bag PsError
getErrorMessages PState
pst))
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 UnhelpfulSpanReason
_ -> (Located Token
t,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) 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 forall a. Ord a => a -> a -> Bool
< RealSrcLoc
start = FilePath
-> RealSrcLoc
-> InputFileBuffer
-> (RealSrcLoc, InputFileBuffer, FilePath)
go FilePath
acc RealSrcLoc
nLoc InputFileBuffer
nBuf
| RealSrcLoc
start forall a. Ord a => a -> a -> Bool
<= RealSrcLoc
loc Bool -> Bool -> Bool
&& RealSrcLoc
loc forall a. Ord a => a -> a -> Bool
< RealSrcLoc
end = FilePath
-> RealSrcLoc
-> InputFileBuffer
-> (RealSrcLoc, InputFileBuffer, FilePath)
go (Char
chforall a. a -> [a] -> [a]
:FilePath
acc) RealSrcLoc
nLoc InputFileBuffer
nBuf
| Bool
otherwise = (RealSrcLoc
loc, InputFileBuffer
buf, 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 = forall {e}.
RealSrcLoc
-> [(GenLocated SrcSpan e, FilePath)] -> FilePath -> FilePath
go RealSrcLoc
startLoc [(Located Token, FilePath)]
ts FilePath
""
where sourceFile :: FastString
sourceFile = [SrcSpan] -> FastString
getFile forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall l e. GenLocated l e -> l
getLoc forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) [(Located Token, FilePath)]
ts
getFile :: [SrcSpan] -> FastString
getFile [] = forall a. FilePath -> a
panic FilePath
"showRichTokenStream: No source file found"
getFile (UnhelpfulSpan UnhelpfulSpanReason
_ : [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
_ [] = forall a. a -> a
id
go RealSrcLoc
loc ((L SrcSpan
span e
_, FilePath
str):[(GenLocated SrcSpan e, FilePath)]
ts)
= case SrcSpan
span of
UnhelpfulSpan UnhelpfulSpanReason
_ -> RealSrcLoc
-> [(GenLocated SrcSpan e, FilePath)] -> FilePath -> FilePath
go RealSrcLoc
loc [(GenLocated SrcSpan e, FilePath)]
ts
RealSrcSpan RealSrcSpan
s Maybe BufSpan
_
| Int
locLine forall a. Eq a => a -> a -> Bool
== Int
tokLine -> ((forall a. Int -> a -> [a]
replicate (Int
tokCol forall a. Num a => a -> a -> a
- Int
locCol) Char
' ') forall a. [a] -> [a] -> [a]
++)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath
str forall a. [a] -> [a] -> [a]
++)
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 -> ((forall a. Int -> a -> [a]
replicate (Int
tokLine forall a. Num a => a -> a -> a
- Int
locLine) Char
'\n') forall a. [a] -> [a] -> [a]
++)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((forall a. Int -> a -> [a]
replicate (Int
tokCol forall a. Num a => a -> a -> a
- Int
1) Char
' ') forall a. [a] -> [a] -> [a]
++)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath
str forall a. [a] -> [a] -> [a]
++)
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 :: forall (m :: * -> *).
GhcMonad m =>
ModuleName -> Maybe FastString -> m Module
findModule ModuleName
mod_name Maybe FastString
maybe_pkg = forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> do
let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
home_unit :: HomeUnit
home_unit = HscEnv -> HomeUnit
hsc_home_unit HscEnv
hsc_env
case Maybe FastString
maybe_pkg of
Just FastString
pkg | Bool -> Bool
not (HomeUnit -> Unit -> Bool
isHomeUnit HomeUnit
home_unit (FastString -> Unit
fsToUnit FastString
pkg)) Bool -> Bool -> Bool
&& FastString
pkg forall a. Eq a => a -> a -> Bool
/= FilePath -> FastString
fsLit FilePath
"this" -> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO 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 -> forall (m :: * -> *) a. Monad m => a -> m a
return Module
m
FindResult
err -> forall (io :: * -> *) a. MonadIO io => WarnMsg -> io a
throwOneError forall a b. (a -> b) -> a -> b
$ HscEnv -> SrcSpan -> ModuleName -> FindResult -> WarnMsg
noModError HscEnv
hsc_env SrcSpan
noSrcSpan ModuleName
mod_name FindResult
err
Maybe FastString
_otherwise -> do
Maybe Module
home <- forall (m :: * -> *). GhcMonad m => ModuleName -> m (Maybe Module)
lookupLoadedHomeModule ModuleName
mod_name
case Maybe Module
home of
Just Module
m -> forall (m :: * -> *) a. Monad m => a -> m a
return Module
m
Maybe Module
Nothing -> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO 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 | Bool -> Bool
not (HomeUnit -> Module -> Bool
isHomeModule HomeUnit
home_unit Module
m) -> forall (m :: * -> *) a. Monad m => a -> m a
return Module
m
| Bool
otherwise -> forall a. DynFlags -> Module -> ModLocation -> IO a
modNotLoadedError DynFlags
dflags Module
m ModLocation
loc
FindResult
err -> forall (io :: * -> *) a. MonadIO io => WarnMsg -> io a
throwOneError forall a b. (a -> b) -> a -> b
$ HscEnv -> SrcSpan -> ModuleName -> FindResult -> WarnMsg
noModError HscEnv
hsc_env SrcSpan
noSrcSpan ModuleName
mod_name FindResult
err
modNotLoadedError :: DynFlags -> Module -> ModLocation -> IO a
modNotLoadedError :: forall a. DynFlags -> Module -> ModLocation -> IO a
modNotLoadedError DynFlags
dflags Module
m ModLocation
loc = forall a. GhcException -> IO a
throwGhcExceptionIO forall a b. (a -> b) -> a -> b
$ FilePath -> GhcException
CmdLineError forall a b. (a -> b) -> a -> b
$ DynFlags -> SDoc -> FilePath
showSDoc DynFlags
dflags forall a b. (a -> b) -> a -> b
$
FilePath -> SDoc
text FilePath
"module is not loaded:" SDoc -> SDoc -> SDoc
<+>
SDoc -> SDoc
quotes (forall a. Outputable a => a -> SDoc
ppr (forall unit. GenModule unit -> ModuleName
moduleName Module
m)) SDoc -> SDoc -> SDoc
<+>
SDoc -> SDoc
parens (FilePath -> SDoc
text (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 :: forall (m :: * -> *).
GhcMonad m =>
ModuleName -> Maybe FastString -> m Module
lookupModule ModuleName
mod_name (Just FastString
pkg) = forall (m :: * -> *).
GhcMonad m =>
ModuleName -> Maybe FastString -> m Module
findModule ModuleName
mod_name (forall a. a -> Maybe a
Just FastString
pkg)
lookupModule ModuleName
mod_name Maybe FastString
Nothing = forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> do
Maybe Module
home <- forall (m :: * -> *). GhcMonad m => ModuleName -> m (Maybe Module)
lookupLoadedHomeModule ModuleName
mod_name
case Maybe Module
home of
Just Module
m -> forall (m :: * -> *) a. Monad m => a -> m a
return Module
m
Maybe Module
Nothing -> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
FindResult
res <- HscEnv -> ModuleName -> Maybe FastString -> IO FindResult
findExposedPackageModule HscEnv
hsc_env ModuleName
mod_name forall a. Maybe a
Nothing
case FindResult
res of
Found ModLocation
_ Module
m -> forall (m :: * -> *) a. Monad m => a -> m a
return Module
m
FindResult
err -> forall (io :: * -> *) a. MonadIO io => WarnMsg -> io a
throwOneError forall a b. (a -> b) -> a -> b
$ HscEnv -> SrcSpan -> ModuleName -> FindResult -> WarnMsg
noModError HscEnv
hsc_env SrcSpan
noSrcSpan ModuleName
mod_name FindResult
err
lookupLoadedHomeModule :: GhcMonad m => ModuleName -> m (Maybe Module)
lookupLoadedHomeModule :: forall (m :: * -> *). GhcMonad m => ModuleName -> m (Maybe Module)
lookupLoadedHomeModule ModuleName
mod_name = forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession 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 -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just (forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module (HomeModInfo -> ModIface
hm_iface HomeModInfo
mod_info)))
Maybe HomeModInfo
_not_a_home_module -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
isModuleTrusted :: GhcMonad m => Module -> m Bool
isModuleTrusted :: forall (m :: * -> *). GhcMonad m => Module -> m Bool
isModuleTrusted Module
m = forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env ->
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO 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 :: forall (m :: * -> *). GhcMonad m => Module -> m (Bool, Set UnitId)
moduleTrustReqs Module
m = forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env ->
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO 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 :: forall (m :: * -> *). GhcMonad m => FilePath -> m ()
setGHCiMonad FilePath
name = forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env -> do
Name
ty <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ HscEnv -> FilePath -> IO Name
hscIsGHCiMonad HscEnv
hsc_env FilePath
name
forall (m :: * -> *). GhcMonad m => (HscEnv -> HscEnv) -> m ()
modifySession 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 :: forall (m :: * -> *). GhcMonad m => m Name
getGHCiMonad = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (InteractiveContext -> Name
ic_monad forall b c a. (b -> c) -> (a -> b) -> a -> c
. HscEnv -> InteractiveContext
hsc_IC) forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
getHistorySpan :: GhcMonad m => History -> m SrcSpan
getHistorySpan :: forall (m :: * -> *). GhcMonad m => History -> m SrcSpan
getHistorySpan History
h = forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env ->
forall (m :: * -> *) a. Monad m => a -> m a
return 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 :: forall (m :: * -> *) a.
GhcMonad m =>
Int -> Bool -> Type -> a -> m Term
obtainTermFromVal Int
bound Bool
force Type
ty a
a = forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env ->
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ 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 :: forall (m :: * -> *). GhcMonad m => Int -> Bool -> Var -> m Term
obtainTermFromId Int
bound Bool
force Var
id = forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env ->
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO 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 :: forall (m :: * -> *). GhcMonad m => Name -> m (Maybe TyThing)
lookupName Name
name =
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
withSession forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env ->
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO 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 forall a. P a -> PState -> ParseResult a
unP P ParsedSource
Parser.parseModule (ParserOpts -> InputFileBuffer -> RealSrcLoc -> PState
initParserState (DynFlags -> ParserOpts
initParserOpts DynFlags
dflags) InputFileBuffer
buf RealSrcLoc
loc) of
PFailed PState
pst ->
let (Bag PsWarning
warns,Bag PsError
errs) = PState -> (Bag PsWarning, Bag PsError)
getMessages PState
pst in
(forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PsWarning -> WarnMsg
pprWarning Bag PsWarning
warns, forall a b. a -> Either a b
Left (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PsError -> WarnMsg
pprError Bag PsError
errs))
POk PState
pst ParsedSource
rdr_module ->
let (Bag PsWarning
warns,Bag PsError
_) = PState -> (Bag PsWarning, Bag PsError)
getMessages PState
pst in
(forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PsWarning -> WarnMsg
pprWarning Bag PsWarning
warns, forall a b. b -> Either a b
Right ParsedSource
rdr_module)
interpretPackageEnv :: Logger -> DynFlags -> IO DynFlags
interpretPackageEnv :: Logger -> DynFlags -> IO DynFlags
interpretPackageEnv Logger
logger DynFlags
dflags = do
Maybe FilePath
mPkgEnv <- forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum forall a b. (a -> b) -> a -> b
$ [
MaybeT IO FilePath
getCmdLineArg forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \FilePath
env -> forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum [
FilePath -> MaybeT IO FilePath
probeNullEnv FilePath
env
, FilePath -> MaybeT IO FilePath
probeEnvFile FilePath
env
, FilePath -> MaybeT IO FilePath
probeEnvName FilePath
env
, forall a. FilePath -> MaybeT IO a
cmdLineError FilePath
env
]
, MaybeT IO FilePath
getEnvVar forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \FilePath
env -> forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum [
FilePath -> MaybeT IO FilePath
probeNullEnv FilePath
env
, FilePath -> MaybeT IO FilePath
probeEnvFile FilePath
env
, FilePath -> MaybeT IO FilePath
probeEnvName FilePath
env
, forall a. FilePath -> MaybeT IO a
envError FilePath
env
]
, MaybeT IO ()
notIfHideAllPackages forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum [
MaybeT IO FilePath
findLocalEnvFile forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FilePath -> MaybeT IO FilePath
probeEnvFile
, FilePath -> MaybeT IO FilePath
probeEnvName FilePath
defaultEnvName
]
]
case Maybe FilePath
mPkgEnv of
Maybe FilePath
Nothing ->
forall (m :: * -> *) a. Monad m => a -> m a
return DynFlags
dflags
Just FilePath
"-" -> do
forall (m :: * -> *) a. Monad m => a -> m a
return DynFlags
dflags
Just FilePath
envfile -> do
FilePath
content <- FilePath -> IO FilePath
readFile FilePath
envfile
Logger -> DynFlags -> SDoc -> IO ()
compilationProgressMsg Logger
logger DynFlags
dflags (FilePath -> SDoc
text FilePath
"Loaded package environment from " SDoc -> SDoc -> SDoc
<> FilePath -> SDoc
text FilePath
envfile)
let ((Errs, Warns, ())
_, DynFlags
dflags') = forall s a. CmdLineP s a -> s -> (a, s)
runCmdLine (forall (m :: * -> *) a. EwM m a -> m (Errs, Warns, a)
runEwM (FilePath -> FilePath -> DynP ()
setFlagsFromEnvFile FilePath
envfile FilePath
content)) DynFlags
dflags
forall (m :: * -> *) a. Monad m => a -> m a
return DynFlags
dflags'
where
archOS :: ArchOS
archOS = Platform -> ArchOS
platformArchOS (DynFlags -> Platform
targetPlatform DynFlags
dflags)
namedEnvPath :: String -> MaybeT IO FilePath
namedEnvPath :: FilePath -> MaybeT IO FilePath
namedEnvPath FilePath
name = do
FilePath
appdir <- FilePath -> ArchOS -> MaybeT IO FilePath
versionedAppDir (DynFlags -> FilePath
programName DynFlags
dflags) ArchOS
archOS
forall (m :: * -> *) a. Monad m => a -> m a
return 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 forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< FilePath -> MaybeT IO FilePath
namedEnvPath FilePath
name
probeEnvFile :: FilePath -> MaybeT IO FilePath
probeEnvFile :: FilePath -> MaybeT IO FilePath
probeEnvFile FilePath
path = do
forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
liftMaybeT (FilePath -> IO Bool
doesFileExist FilePath
path)
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
path
probeNullEnv :: FilePath -> MaybeT IO FilePath
probeNullEnv :: FilePath -> MaybeT IO FilePath
probeNullEnv FilePath
"-" = forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
"-"
probeNullEnv FilePath
_ = forall (m :: * -> *) a. MonadPlus m => m a
mzero
getCmdLineArg :: MaybeT IO String
getCmdLineArg :: MaybeT IO FilePath
getCmdLineArg = forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return 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 <- forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
liftMaybeT forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> m (Either e a)
MC.try forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
getEnv FilePath
"GHC_ENVIRONMENT"
case Either IOError FilePath
mvar of
Right FilePath
var -> forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
var
Left IOError
err -> if IOError -> Bool
isDoesNotExistError IOError
err then forall (m :: * -> *) a. MonadPlus m => m a
mzero
else forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
liftMaybeT forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => e -> IO a
throwIO IOError
err
notIfHideAllPackages :: MaybeT IO ()
notIfHideAllPackages :: MaybeT IO ()
notIfHideAllPackages =
forall (f :: * -> *). Alternative f => Bool -> f ()
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
<.> ArchOS -> FilePath
versionedFilePath ArchOS
archOS
findLocalEnvFile :: MaybeT IO FilePath
findLocalEnvFile :: MaybeT IO FilePath
findLocalEnvFile = do
FilePath
curdir <- forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
liftMaybeT IO FilePath
getCurrentDirectory
FilePath
homedir <- 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 forall a. Eq a => a -> a -> Bool
== FilePath
homedir
= forall (m :: * -> *) a. MonadPlus m => m a
mzero
probe FilePath
dir = do
let file :: FilePath
file = FilePath
dir FilePath -> FilePath -> FilePath
</> FilePath
localEnvFileName
Bool
exists <- forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
liftMaybeT (FilePath -> IO Bool
doesFileExist FilePath
file)
if Bool
exists
then forall (m :: * -> *) a. Monad m => a -> m a
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 :: forall a. FilePath -> MaybeT IO a
cmdLineError FilePath
env = forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
liftMaybeT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. GhcException -> IO a
throwGhcExceptionIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> GhcException
CmdLineError forall a b. (a -> b) -> a -> b
$
FilePath
"Package environment " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show FilePath
env forall a. [a] -> [a] -> [a]
++ FilePath
" not found"
envError :: String -> MaybeT IO a
envError :: forall a. FilePath -> MaybeT IO a
envError FilePath
env = forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
liftMaybeT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. GhcException -> IO a
throwGhcExceptionIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> GhcException
CmdLineError forall a b. (a -> b) -> a -> b
$
FilePath
"Package environment "
forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show FilePath
env
forall a. [a] -> [a] -> [a]
++ FilePath
" (specified in GHC_ENVIRONMENT) not found"
newtype GhcApiError = GhcApiError String
instance Show GhcApiError where
show :: GhcApiError -> FilePath
show (GhcApiError FilePath
msg) = FilePath
msg
instance Exception GhcApiError
mkApiErr :: DynFlags -> SDoc -> GhcApiError
mkApiErr :: DynFlags -> SDoc -> GhcApiError
mkApiErr DynFlags
dflags SDoc
msg = FilePath -> GhcApiError
GhcApiError (DynFlags -> SDoc -> FilePath
showSDoc DynFlags
dflags SDoc
msg)