ghc-6.12.3: The GHC APISource codeContentsIndex
HscMain
Description

Main driver for the compiling plain Haskell source code.

This module implements compilation of a Haskell-only source file. It is not concerned with preprocessing of source files; this is handled in DriverPipeline.

Synopsis
newHscEnv :: GhcApiCallbacks -> DynFlags -> IO HscEnv
hscCmmFile :: GhcMonad m => HscEnv -> FilePath -> m ()
hscParseIdentifier :: GhcMonad m => DynFlags -> String -> m (Located RdrName)
hscSimplify :: GhcMonad m => ModGuts -> m ModGuts
hscNormalIface :: GhcMonad m => ModGuts -> Maybe Fingerprint -> m (ModIface, Bool, ModDetails, CgGuts)
hscWriteIface :: GhcMonad m => ModIface -> Bool -> ModSummary -> m ()
hscGenHardCode :: GhcMonad m => CgGuts -> ModSummary -> m Bool
hscStmt :: GhcMonad m => HscEnv -> String -> m (Maybe ([Id], HValue))
hscTcExpr :: GhcMonad m => HscEnv -> String -> m Type
hscKcType :: GhcMonad m => HscEnv -> String -> m Kind
compileExpr :: HscEnv -> SrcSpan -> CoreExpr -> IO HValue
data HsCompiler a = HsCompiler {
hscCompile :: GhcMonad m => HscEnv -> ModSummary -> Bool -> Maybe ModIface -> Maybe (Int, Int) -> m a
hscNoRecomp :: GhcMonad m => ModIface -> m a
hscRecompile :: GhcMonad m => ModSummary -> Maybe Fingerprint -> m a
hscBackend :: GhcMonad m => TcGblEnv -> ModSummary -> Maybe Fingerprint -> m a
hscGenBootOutput :: GhcMonad m => TcGblEnv -> ModSummary -> Maybe Fingerprint -> m a
hscGenOutput :: GhcMonad m => ModGuts -> ModSummary -> Maybe Fingerprint -> m a
}
hscOneShotCompiler :: HsCompiler OneShotResult
hscNothingCompiler :: HsCompiler NothingResult
hscInteractiveCompiler :: HsCompiler InteractiveResult
hscBatchCompiler :: HsCompiler BatchResult
hscCompileOneShot :: Compiler OneShotResult
hscCompileBatch :: Compiler (HscStatus, ModIface, ModDetails)
hscCompileNothing :: Compiler (HscStatus, ModIface, ModDetails)
hscCompileInteractive :: Compiler (InteractiveStatus, ModIface, ModDetails)
data HscStatus' a
= HscNoRecomp
| HscRecomp Bool a
type InteractiveStatus = HscStatus' (Maybe (CompiledByteCode, ModBreaks))
type HscStatus = HscStatus' ()
hscParse :: GhcMonad m => ModSummary -> m (Located (HsModule RdrName))
hscTypecheck :: GhcMonad m => ModSummary -> Located (HsModule RdrName) -> m TcGblEnv
hscTypecheckRename :: GhcMonad m => ModSummary -> Located (HsModule RdrName) -> m (TcGblEnv, RenamedStuff)
hscDesugar :: GhcMonad m => ModSummary -> TcGblEnv -> m ModGuts
makeSimpleIface :: GhcMonad m => Maybe ModIface -> TcGblEnv -> ModDetails -> m (ModIface, Bool)
makeSimpleDetails :: GhcMonad m => TcGblEnv -> m ModDetails
Documentation
newHscEnv :: GhcApiCallbacks -> DynFlags -> IO HscEnvSource
hscCmmFile :: GhcMonad m => HscEnv -> FilePath -> m ()Source
hscParseIdentifier :: GhcMonad m => DynFlags -> String -> m (Located RdrName)Source
hscSimplify :: GhcMonad m => ModGuts -> m ModGutsSource
hscNormalIface :: GhcMonad m => ModGuts -> Maybe Fingerprint -> m (ModIface, Bool, ModDetails, CgGuts)Source
hscWriteIface :: GhcMonad m => ModIface -> Bool -> ModSummary -> m ()Source
hscGenHardCodeSource
:: GhcMonad m
=> CgGuts
-> ModSummary
-> m BoolTrue = stub.c exists
Compile to hard-code.
hscStmtSource
:: GhcMonad m
=> HscEnv
-> String
-> m (Maybe ([Id], HValue))Nothing == empty statement (or comment only), but no parse error
hscTcExpr :: GhcMonad m => HscEnv -> String -> m TypeSource
hscKcTypeSource
:: GhcMonad m
=> HscEnv
-> StringThe type
-> m Kind
Find the kind of a type
compileExpr :: HscEnv -> SrcSpan -> CoreExpr -> IO HValueSource
data HsCompiler a Source
Constructors
HsCompiler
hscCompile :: GhcMonad m => HscEnv -> ModSummary -> Bool -> Maybe ModIface -> Maybe (Int, Int) -> m aThe main interface.
hscNoRecomp :: GhcMonad m => ModIface -> m aCalled when no recompilation is necessary.
hscRecompile :: GhcMonad m => ModSummary -> Maybe Fingerprint -> m aCalled to recompile the module.
hscBackend :: GhcMonad m => TcGblEnv -> ModSummary -> Maybe Fingerprint -> m a
hscGenBootOutput :: GhcMonad m => TcGblEnv -> ModSummary -> Maybe Fingerprint -> m aCode generation for Boot modules.
hscGenOutput :: GhcMonad m => ModGuts -> ModSummary -> Maybe Fingerprint -> m aCode generation for normal modules.
hscOneShotCompiler :: HsCompiler OneShotResultSource
hscNothingCompiler :: HsCompiler NothingResultSource
hscInteractiveCompiler :: HsCompiler InteractiveResultSource
hscBatchCompiler :: HsCompiler BatchResultSource
hscCompileOneShot :: Compiler OneShotResultSource
hscCompileBatch :: Compiler (HscStatus, ModIface, ModDetails)Source
hscCompileNothing :: Compiler (HscStatus, ModIface, ModDetails)Source
hscCompileInteractive :: Compiler (InteractiveStatus, ModIface, ModDetails)Source
data HscStatus' a Source
Constructors
HscNoRecomp
HscRecomp Bool a
type InteractiveStatus = HscStatus' (Maybe (CompiledByteCode, ModBreaks))Source
type HscStatus = HscStatus' ()Source
hscParse :: GhcMonad m => ModSummary -> m (Located (HsModule RdrName))Source
parse a file, returning the abstract syntax
hscTypecheck :: GhcMonad m => ModSummary -> Located (HsModule RdrName) -> m TcGblEnvSource
Rename and typecheck a module
hscTypecheckRename :: GhcMonad m => ModSummary -> Located (HsModule RdrName) -> m (TcGblEnv, RenamedStuff)Source
Rename and typecheck a module, additionally returning the renamed syntax
hscDesugar :: GhcMonad m => ModSummary -> TcGblEnv -> m ModGutsSource
Convert a typechecked module to Core
makeSimpleIface :: GhcMonad m => Maybe ModIface -> TcGblEnv -> ModDetails -> m (ModIface, Bool)Source
Make a ModIface from the results of typechecking. Used when not optimising, and the interface doesn't need to contain any unfoldings or other cross-module optimisation info. ToDo: the old interface is only needed to get the version numbers, we should use fingerprint versions instead.
makeSimpleDetails :: GhcMonad m => TcGblEnv -> m ModDetailsSource
Make a ModDetails from the results of typechecking. Used when typechecking only, as opposed to full compilation.
Produced by Haddock version 2.6.1