Safe Haskell | None |
---|---|
Language | Haskell98 |
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).
Warning messages are dealt with consistently throughout this API:
during compilation warnings are collected, and before any function
in HscMain
returns, the warnings are either printed, or turned
into a real compialtion error 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
- hscCompileOneShot :: HscEnv -> FilePath -> ModSummary -> SourceModified -> IO HscStatus
- hscCompileCmmFile :: HscEnv -> FilePath -> FilePath -> IO ()
- hscCompileCore :: HscEnv -> Bool -> SafeHaskellMode -> ModSummary -> CoreProgram -> FilePath -> FilePath -> IO ()
- genericHscCompileGetFrontendResult :: Bool -> Maybe TcGblEnv -> Maybe Messager -> HscEnv -> ModSummary -> SourceModified -> Maybe ModIface -> (Int, Int) -> IO (Either ModIface (TcGblEnv, Maybe Fingerprint))
- genModDetails :: HscEnv -> ModIface -> IO ModDetails
- hscSimpleIface :: HscEnv -> TcGblEnv -> Maybe Fingerprint -> IO (ModIface, Bool, ModDetails)
- hscWriteIface :: DynFlags -> ModIface -> Bool -> ModSummary -> IO ()
- hscNormalIface :: HscEnv -> FilePath -> 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, ModBreaks)
- 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
- hscParseIdentifier :: HscEnv -> String -> IO (Located RdrName)
- hscTcRcLookupName :: HscEnv -> Name -> IO (Maybe TyThing)
- hscTcRnGetInfo :: HscEnv -> Name -> IO (Maybe (TyThing, Fixity, [ClsInst], [FamInst]))
- hscCheckSafe :: HscEnv -> Module -> SrcSpan -> IO Bool
- hscGetSafe :: HscEnv -> Module -> SrcSpan -> IO (Bool, [PackageId])
- hscIsGHCiMonad :: HscEnv -> String -> IO Name
- hscGetModuleInterface :: HscEnv -> Module -> IO ModIface
- hscRnImportDecls :: HscEnv -> [LImportDecl RdrName] -> IO GlobalRdrEnv
- hscTcRnLookupRdrName :: HscEnv -> RdrName -> IO [Name]
- hscStmt :: HscEnv -> String -> IO (Maybe ([Id], IO [HValue], FixityEnv))
- hscStmtWithLocation :: HscEnv -> String -> String -> Int -> IO (Maybe ([Id], IO [HValue], 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)
- hscCompileCoreExpr :: HscEnv -> SrcSpan -> CoreExpr -> IO HValue
- hscCompileCoreExpr' :: HscEnv -> SrcSpan -> CoreExpr -> IO HValue
- 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' :: FilePath -> ModGuts -> Maybe Fingerprint -> Hsc (ModIface, Bool, ModDetails, CgGuts)
- oneShotMsg :: HscEnv -> RecompileRequired -> IO ()
- hscFileFrontEnd :: ModSummary -> Hsc TcGblEnv
- genericHscFrontend :: ModSummary -> Hsc TcGblEnv
- 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
hscCompileOneShot :: HscEnv -> FilePath -> ModSummary -> SourceModified -> IO HscStatus Source
hscCompileCore :: HscEnv -> Bool -> SafeHaskellMode -> ModSummary -> CoreProgram -> FilePath -> FilePath -> IO () Source
genericHscCompileGetFrontendResult :: Bool -> Maybe TcGblEnv -> Maybe Messager -> HscEnv -> ModSummary -> SourceModified -> Maybe ModIface -> (Int, Int) -> IO (Either ModIface (TcGblEnv, Maybe Fingerprint)) Source
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 -> FilePath -> ModGuts -> Maybe Fingerprint -> IO (ModIface, Bool, ModDetails, CgGuts) Source
Compile to hard-code.
hscInteractive :: HscEnv -> CgGuts -> ModSummary -> IO (Maybe FilePath, CompiledByteCode, ModBreaks) 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.
Support for interactive evaluation
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, [PackageId]) Source
Return if a module is trusted and the pkgs it depends on to be trusted.
hscRnImportDecls :: HscEnv -> [LImportDecl RdrName] -> IO GlobalRdrEnv Source
Rename some import declarations
hscTcRnLookupRdrName :: HscEnv -> RdrName -> IO [Name] Source
Lookup things in the compiler's environment
hscStmt :: HscEnv -> String -> IO (Maybe ([Id], IO [HValue], 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], IO [HValue], 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
Low-level exports for hooks
hscSimplify' :: ModGuts -> Hsc ModGuts 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' :: FilePath -> ModGuts -> Maybe Fingerprint -> Hsc (ModIface, Bool, ModDetails, CgGuts) Source
oneShotMsg :: HscEnv -> RecompileRequired -> IO () Source
dumpIfaceStats :: HscEnv -> IO () Source