Safe Haskell | None |
---|
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 Compiler result = HscEnv -> ModSummary -> SourceModified -> Maybe ModIface -> Maybe (Int, Int) -> IO result
- data HscStatus' a
- = HscNoRecomp
- | HscRecomp (Maybe FilePath) a
- type InteractiveStatus = HscStatus' (Maybe (CompiledByteCode, ModBreaks))
- type HscStatus = HscStatus' ()
- hscCompileOneShot :: Compiler OneShotResult
- hscCompileBatch :: Compiler (HscStatus, ModIface, ModDetails)
- hscCompileNothing :: Compiler (HscStatus, ModIface, ModDetails)
- hscCompileInteractive :: Compiler (InteractiveStatus, ModIface, ModDetails)
- hscCompileCmmFile :: HscEnv -> FilePath -> IO ()
- hscCompileCore :: HscEnv -> Bool -> SafeHaskellMode -> ModSummary -> CoreProgram -> IO ()
- 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
- hscOneShotBackendOnly :: TcGblEnv -> Compiler OneShotResult
- hscBatchBackendOnly :: TcGblEnv -> Compiler BatchResult
- hscNothingBackendOnly :: TcGblEnv -> Compiler NothingResult
- hscInteractiveBackendOnly :: TcGblEnv -> Compiler InteractiveResult
- hscParseIdentifier :: HscEnv -> String -> IO (Located RdrName)
- hscTcRcLookupName :: HscEnv -> Name -> IO (Maybe TyThing)
- hscTcRnGetInfo :: HscEnv -> Name -> IO (Maybe (TyThing, Fixity, [ClsInst]))
- 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
Making an HscEnv
Compiling complete source files
type Compiler result = HscEnv -> ModSummary -> SourceModified -> Maybe ModIface -> Maybe (Int, Int) -> IO resultSource
data HscStatus' a Source
Status of a compilation to hard-code or nothing.
type InteractiveStatus = HscStatus' (Maybe (CompiledByteCode, ModBreaks))Source
type HscStatus = HscStatus' ()Source
hscCompileOneShot :: Compiler OneShotResultSource
hscCompileBatch :: Compiler (HscStatus, ModIface, ModDetails)Source
Compile Haskell, boot and extCore in batch mode.
hscCompileCmmFile :: HscEnv -> FilePath -> IO ()Source
hscCompileCore :: HscEnv -> Bool -> SafeHaskellMode -> ModSummary -> CoreProgram -> IO ()Source
Running passes separately
hscParse :: HscEnv -> ModSummary -> IO HsParsedModuleSource
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 ModGutsSource
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 ModDetailsSource
Make a ModDetails
from the results of typechecking. Used when
typechecking only, as opposed to full compilation.
Backends
hscOneShotBackendOnly :: TcGblEnv -> Compiler OneShotResultSource
hscBatchBackendOnly :: TcGblEnv -> Compiler BatchResultSource
hscNothingBackendOnly :: TcGblEnv -> Compiler NothingResultSource
hscInteractiveBackendOnly :: TcGblEnv -> Compiler InteractiveResultSource
Support for interactive evaluation
hscCheckSafe :: HscEnv -> Module -> SrcSpan -> IO BoolSource
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 GlobalRdrEnvSource
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)