Safe Haskell | None |
---|---|
Language | Haskell2010 |
Main API for compiling plain Haskell source code.
This module implements compilation of a Haskell source. It is not concerned with preprocessing of source files; this is handled in DriverPipeline.
There are various entry points depending on what mode we're in:
"batch" mode (--make
), "one-shot" mode (-c
, -S
etc.), and
"interactive" mode (GHCi). There are also entry points for
individual passes: parsing, typechecking/renaming, desugaring, and
simplification.
All the functions here take an HscEnv
as a parameter, but none of
them return a new one: HscEnv
is treated as an immutable value
from here on in (although it has mutable components, for the
caches).
We use the Hsc monad to deal with warning messages consistently:
specifically, while executing within an Hsc monad, warnings are
collected. When a Hsc monad returns to an IO monad, the
warnings are printed, or compilation aborts if the -Werror
flag is enabled.
(c) The GRASP/AQUA Project, Glasgow University, 1993-2000
- newHscEnv :: DynFlags -> IO HscEnv
- type Messager = HscEnv -> (Int, Int) -> RecompileRequired -> ModSummary -> IO ()
- batchMsg :: Messager
- data HscStatus
- hscIncrementalCompile :: Bool -> Maybe TcGblEnv -> Maybe Messager -> HscEnv -> ModSummary -> SourceModified -> Maybe ModIface -> (Int, Int) -> IO (HscStatus, HomeModInfo)
- hscCompileCmmFile :: HscEnv -> FilePath -> FilePath -> IO ()
- hscCompileCore :: HscEnv -> Bool -> SafeHaskellMode -> ModSummary -> CoreProgram -> FilePath -> IO ()
- hscIncrementalFrontend :: Bool -> Maybe TcGblEnv -> Maybe Messager -> ModSummary -> SourceModified -> Maybe ModIface -> (Int, Int) -> Hsc (Either ModIface (FrontendResult, Maybe Fingerprint))
- genModDetails :: HscEnv -> ModIface -> IO ModDetails
- hscSimpleIface :: HscEnv -> TcGblEnv -> Maybe Fingerprint -> IO (ModIface, Bool, ModDetails)
- hscWriteIface :: DynFlags -> ModIface -> Bool -> ModSummary -> IO ()
- hscNormalIface :: HscEnv -> ModGuts -> Maybe Fingerprint -> IO (ModIface, Bool, ModDetails, CgGuts)
- hscGenHardCode :: HscEnv -> CgGuts -> ModSummary -> FilePath -> IO (FilePath, Maybe FilePath)
- hscInteractive :: HscEnv -> CgGuts -> ModSummary -> IO (Maybe FilePath, CompiledByteCode)
- hscParse :: HscEnv -> ModSummary -> IO HsParsedModule
- hscTypecheckRename :: HscEnv -> ModSummary -> HsParsedModule -> IO (TcGblEnv, RenamedStuff)
- hscDesugar :: HscEnv -> ModSummary -> TcGblEnv -> IO ModGuts
- makeSimpleIface :: HscEnv -> Maybe ModIface -> TcGblEnv -> ModDetails -> IO (ModIface, Bool)
- makeSimpleDetails :: HscEnv -> TcGblEnv -> IO ModDetails
- hscSimplify :: HscEnv -> ModGuts -> IO ModGuts
- hscCheckSafe :: HscEnv -> Module -> SrcSpan -> IO Bool
- hscGetSafe :: HscEnv -> Module -> SrcSpan -> IO (Bool, [UnitId])
- hscParseIdentifier :: HscEnv -> String -> IO (Located RdrName)
- hscTcRcLookupName :: HscEnv -> Name -> IO (Maybe TyThing)
- hscTcRnGetInfo :: HscEnv -> Name -> IO (Maybe (TyThing, Fixity, [ClsInst], [FamInst]))
- hscIsGHCiMonad :: HscEnv -> String -> IO Name
- hscGetModuleInterface :: HscEnv -> Module -> IO ModIface
- hscRnImportDecls :: HscEnv -> [LImportDecl RdrName] -> IO GlobalRdrEnv
- hscTcRnLookupRdrName :: HscEnv -> Located RdrName -> IO [Name]
- hscStmt :: HscEnv -> String -> IO (Maybe ([Id], ForeignHValue, FixityEnv))
- hscStmtWithLocation :: HscEnv -> String -> String -> Int -> IO (Maybe ([Id], ForeignHValue, FixityEnv))
- hscParsedStmt :: HscEnv -> GhciLStmt RdrName -> IO (Maybe ([Id], ForeignHValue, FixityEnv))
- hscDecls :: HscEnv -> String -> IO ([TyThing], InteractiveContext)
- hscDeclsWithLocation :: HscEnv -> String -> String -> Int -> IO ([TyThing], InteractiveContext)
- hscTcExpr :: HscEnv -> String -> IO Type
- hscImport :: HscEnv -> String -> IO (ImportDecl RdrName)
- hscKcType :: HscEnv -> Bool -> String -> IO (Type, Kind)
- hscParseExpr :: String -> Hsc (LHsExpr RdrName)
- hscCompileCoreExpr :: HscEnv -> SrcSpan -> CoreExpr -> IO ForeignHValue
- hscCompileCoreExpr' :: HscEnv -> SrcSpan -> CoreExpr -> IO ForeignHValue
- hscParse' :: ModSummary -> Hsc HsParsedModule
- hscSimplify' :: ModGuts -> Hsc ModGuts
- hscDesugar' :: ModLocation -> TcGblEnv -> Hsc ModGuts
- tcRnModule' :: HscEnv -> ModSummary -> Bool -> HsParsedModule -> Hsc TcGblEnv
- getHscEnv :: Hsc HscEnv
- hscSimpleIface' :: TcGblEnv -> Maybe Fingerprint -> Hsc (ModIface, Bool, ModDetails)
- hscNormalIface' :: ModGuts -> Maybe Fingerprint -> Hsc (ModIface, Bool, ModDetails, CgGuts)
- oneShotMsg :: HscEnv -> RecompileRequired -> IO ()
- hscFileFrontEnd :: ModSummary -> Hsc TcGblEnv
- genericHscFrontend :: ModSummary -> Hsc FrontendResult
- dumpIfaceStats :: HscEnv -> IO ()
Making an HscEnv
Compiling complete source files
type Messager = HscEnv -> (Int, Int) -> RecompileRequired -> ModSummary -> IO () Source #
Status of a compilation to hard-code
hscIncrementalCompile :: Bool -> Maybe TcGblEnv -> Maybe Messager -> HscEnv -> ModSummary -> SourceModified -> Maybe ModIface -> (Int, Int) -> IO (HscStatus, HomeModInfo) Source #
hscCompileCore :: HscEnv -> Bool -> SafeHaskellMode -> ModSummary -> CoreProgram -> FilePath -> IO () Source #
hscIncrementalFrontend :: Bool -> Maybe TcGblEnv -> Maybe Messager -> ModSummary -> SourceModified -> Maybe ModIface -> (Int, Int) -> Hsc (Either ModIface (FrontendResult, Maybe Fingerprint)) Source #
This function runs GHC's frontend with recompilation avoidance. Specifically, it checks if recompilation is needed, and if it is, it parses and typechecks the input module. It does not write out the results of typechecking (See compileOne and hscIncrementalCompile).
genModDetails :: HscEnv -> ModIface -> IO ModDetails Source #
hscSimpleIface :: HscEnv -> TcGblEnv -> Maybe Fingerprint -> IO (ModIface, Bool, ModDetails) Source #
hscWriteIface :: DynFlags -> ModIface -> Bool -> ModSummary -> IO () Source #
hscNormalIface :: HscEnv -> ModGuts -> Maybe Fingerprint -> IO (ModIface, Bool, ModDetails, CgGuts) Source #
Compile to hard-code.
hscInteractive :: HscEnv -> CgGuts -> ModSummary -> IO (Maybe FilePath, CompiledByteCode) Source #
Running passes separately
hscParse :: HscEnv -> ModSummary -> IO HsParsedModule Source #
parse a file, returning the abstract syntax
hscTypecheckRename :: HscEnv -> ModSummary -> HsParsedModule -> IO (TcGblEnv, RenamedStuff) Source #
Rename and typecheck a module, additionally returning the renamed syntax
hscDesugar :: HscEnv -> ModSummary -> TcGblEnv -> IO ModGuts Source #
Convert a typechecked module to Core
makeSimpleIface :: HscEnv -> Maybe ModIface -> TcGblEnv -> ModDetails -> IO (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 :: HscEnv -> TcGblEnv -> IO ModDetails Source #
Make a ModDetails
from the results of typechecking. Used when
typechecking only, as opposed to full compilation.
Safe Haskell
hscCheckSafe :: HscEnv -> Module -> SrcSpan -> IO Bool Source #
Check that a module is safe to import.
We return True to indicate the import is safe and False otherwise although in the False case an exception may be thrown first.
hscGetSafe :: HscEnv -> Module -> SrcSpan -> IO (Bool, [UnitId]) Source #
Return if a module is trusted and the pkgs it depends on to be trusted.
Support for interactive evaluation
hscRnImportDecls :: HscEnv -> [LImportDecl RdrName] -> IO GlobalRdrEnv Source #
Rename some import declarations
hscTcRnLookupRdrName :: HscEnv -> Located RdrName -> IO [Name] Source #
Lookup things in the compiler's environment
hscStmt :: HscEnv -> String -> IO (Maybe ([Id], ForeignHValue, FixityEnv)) Source #
Compile a stmt all the way to an HValue, but don't run it
We return Nothing to indicate an empty statement (or comment only), not a parse error.
:: HscEnv | |
-> String | The statement |
-> String | The source |
-> Int | Starting line |
-> IO (Maybe ([Id], ForeignHValue, FixityEnv)) |
Compile a stmt all the way to an HValue, but don't run it
We return Nothing to indicate an empty statement (or comment only), not a parse error.
:: HscEnv | |
-> String | The statement |
-> IO ([TyThing], InteractiveContext) |
Compile a decls
:: HscEnv | |
-> String | The statement |
-> String | The source |
-> Int | Starting line |
-> IO ([TyThing], InteractiveContext) |
Compile a decls
Typecheck an expression (but don't run it) Returns its most general type
:: HscEnv | |
-> Bool | Normalise the type |
-> String | The type as a string |
-> IO (Type, Kind) | Resulting type (possibly normalised) and kind |
Find the kind of a type Currently this does *not* generalise the kinds of the type
hscCompileCoreExpr :: HscEnv -> SrcSpan -> CoreExpr -> IO ForeignHValue Source #
Low-level exports for hooks
hscCompileCoreExpr' :: HscEnv -> SrcSpan -> CoreExpr -> IO ForeignHValue Source #
hscParse' :: ModSummary -> Hsc HsParsedModule Source #
hscDesugar' :: ModLocation -> TcGblEnv -> Hsc ModGuts Source #
tcRnModule' :: HscEnv -> ModSummary -> Bool -> HsParsedModule -> Hsc TcGblEnv Source #
hscSimpleIface' :: TcGblEnv -> Maybe Fingerprint -> Hsc (ModIface, Bool, ModDetails) Source #
hscNormalIface' :: ModGuts -> Maybe Fingerprint -> Hsc (ModIface, Bool, ModDetails, CgGuts) Source #
oneShotMsg :: HscEnv -> RecompileRequired -> IO () Source #
hscFileFrontEnd :: ModSummary -> Hsc TcGblEnv Source #
Given a ModSummary
, parses and typechecks it, returning the
TcGblEnv
resulting from type-checking.
dumpIfaceStats :: HscEnv -> IO () Source #