Safe Haskell | None |
---|---|
Language | Haskell2010 |
All the CPP for GHC version compability should live in this module.
Synopsis
- ghcVersion :: String
- type WarnFlags = EnumSet WarningFlag
- emptyWarnFlags :: WarnFlags
- makeUserStyle :: DynFlags -> PrintUnqualified -> PprStyle
- data PprStyle
- parseTargetFiles :: DynFlags -> [String] -> (DynFlags, [(String, Maybe Phase)], [String])
- modifySession :: GhcMonad m => (HscEnv -> HscEnv) -> m ()
- reflectGhc :: Ghc a -> Session -> IO a
- data Session = Session !(IORef HscEnv)
- getHscEnv :: Hsc HscEnv
- batchMsg :: Messager
- set_hsc_dflags :: DynFlags -> HscEnv -> HscEnv
- overPkgDbRef :: (FilePath -> FilePath) -> PackageDBFlag -> PackageDBFlag
- guessTarget :: GhcMonad m => String -> Maybe Phase -> m Target
- setNoCode :: DynFlags -> DynFlags
- getModSummaries :: ModuleGraph -> [ModSummary]
- mapOverIncludePaths :: (FilePath -> FilePath) -> DynFlags -> DynFlags
- getLogger :: HscEnv -> Logger
- pattern RealSrcSpan :: RealSrcSpan -> SrcSpan
- type LExpression = LHsExpr GhcTc
- type LBinding = LHsBind GhcTc
- type LPattern = LPat GhcTc
- inTypes :: MatchGroup GhcTc LExpression -> [Type]
- outType :: MatchGroup GhcTc LExpression -> Type
- catch :: (MonadCatch m, Exception e) => m a -> (e -> m a) -> m a
- bracket :: ExceptionMonad m => m a -> (a -> m c) -> (a -> m b) -> m b
- handle :: (ExceptionMonad m, Exception e) => (e -> m a) -> m a -> m a
- pageMode :: Mode
- oneLineMode :: Mode
- initializePluginsForModSummary :: HscEnv -> ModSummary -> IO (Int, [ModuleName], ModSummary)
- setFrontEndHooks :: Maybe (ModSummary -> Hsc FrontendResult) -> HscEnv -> HscEnv
- updOptLevel :: Int -> DynFlags -> DynFlags
- setWayDynamicIfHostIsDynamic :: DynFlags -> DynFlags
- gopt_set :: DynFlags -> GeneralFlag -> DynFlags
- parseDynamicFlags :: MonadIO m => Logger -> DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn])
- hostIsDynamic :: Bool
- getModuleName :: (a, b) -> a
- getTyThing :: (a, b, c, d, e) -> a
- fixInfo :: (a, b, c, d, e) -> (a, b, c, d)
- data FrontendResult = FrontendTypecheck TcGblEnv
- data Hsc a
- mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph
- mgModSummaries :: ModuleGraph -> [ModSummary]
- unsetLogAction :: GhcMonad m => m ()
Documentation
ghcVersion :: String Source #
Warnings, Doc Compat
type WarnFlags = EnumSet WarningFlag Source #
makeUserStyle :: DynFlags -> PrintUnqualified -> PprStyle Source #
Argument parsing
Ghc Monad
modifySession :: GhcMonad m => (HscEnv -> HscEnv) -> m () #
Set the current session to the result of applying the current session to the argument.
reflectGhc :: Ghc a -> Session -> IO a #
Reflect a computation in the Ghc
monad into the IO
monad.
You can use this to call functions returning an action in the Ghc
monad
inside an IO
action. This is needed for some (too restrictive) callback
arguments of some library functions:
libFunc :: String -> (Int -> IO a) -> IO a ghcFunc :: Int -> Ghc a ghcFuncUsingLibFunc :: String -> Ghc a -> Ghc a ghcFuncUsingLibFunc str = reifyGhc $ \s -> libFunc $ \i -> do reflectGhc (ghcFunc i) s
The Session is a handle to the complete state of a compilation session. A compilation session consists of a set of modules constituting the current program or library, the context for interactive evaluation, and various caches.
Hsc Monad
Driver compat
HscEnv Compat
overPkgDbRef :: (FilePath -> FilePath) -> PackageDBFlag -> PackageDBFlag Source #
getModSummaries :: ModuleGraph -> [ModSummary] Source #
AST compat
pattern RealSrcSpan :: RealSrcSpan -> SrcSpan Source #
type LExpression = LHsExpr GhcTc Source #
inTypes :: MatchGroup GhcTc LExpression -> [Type] Source #
outType :: MatchGroup GhcTc LExpression -> Type Source #
Exceptions
catch :: (MonadCatch m, Exception e) => m a -> (e -> m a) -> m a Source #
bracket :: ExceptionMonad m => m a -> (a -> m c) -> (a -> m b) -> m b Source #
handle :: (ExceptionMonad m, Exception e) => (e -> m a) -> m a -> m a Source #
Doc Gap functions
oneLineMode :: Mode Source #
DynFlags compat
initializePluginsForModSummary :: HscEnv -> ModSummary -> IO (Int, [ModuleName], ModSummary) Source #
setFrontEndHooks :: Maybe (ModSummary -> Hsc FrontendResult) -> HscEnv -> HscEnv Source #
updOptLevel :: Int -> DynFlags -> DynFlags #
Sets the DynFlags
to be appropriate to the optimisation level
parseDynamicFlags :: MonadIO m => Logger -> DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn]) Source #
Platform constants
hostIsDynamic :: Bool Source #
misc
getModuleName :: (a, b) -> a Source #
getTyThing :: (a, b, c, d, e) -> a Source #
data FrontendResult #
FrontendResult
describes the result of running the
frontend of a Haskell module. Usually, you'll get
a FrontendTypecheck
, since running the frontend involves
typechecking a program, but for an hs-boot merge you'll
just get a ModIface, since no actual typechecking occurred.
This data type really should be in HscTypes, but it needs to have a TcGblEnv which is only defined here.
Instances
Monad Hsc | |
Functor Hsc | |
Applicative Hsc | |
MonadIO Hsc | |
HasDynFlags Hsc | |
Defined in HscTypes getDynFlags :: Hsc DynFlags # |
mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph #
Map a function f
over all the ModSummaries
.
To preserve invariants f
can't change the isBoot status.
mgModSummaries :: ModuleGraph -> [ModSummary] #
unsetLogAction :: GhcMonad m => m () Source #