Safe Haskell | None |
---|---|
Language | Haskell98 |
- oneShot :: HscEnv -> Phase -> [(String, Maybe Phase)] -> IO ()
- compileFile :: HscEnv -> Phase -> (FilePath, Maybe Phase) -> IO FilePath
- linkBinary :: DynFlags -> [FilePath] -> [PackageId] -> IO ()
- preprocess :: HscEnv -> (FilePath, Maybe Phase) -> IO (DynFlags, FilePath)
- compileOne :: HscEnv -> ModSummary -> Int -> Int -> Maybe ModIface -> Maybe Linkable -> SourceModified -> IO HomeModInfo
- compileOne' :: Maybe TcGblEnv -> Maybe Messager -> HscEnv -> ModSummary -> Int -> Int -> Maybe ModIface -> Maybe Linkable -> SourceModified -> IO HomeModInfo
- link :: GhcLink -> DynFlags -> Bool -> HomePackageTable -> IO SuccessFlag
- data PhasePlus
- newtype CompPipeline a = P {}
- data PipeEnv = PipeEnv {}
- data PipeState = PipeState {}
- phaseOutputFilename :: Phase -> CompPipeline FilePath
- getPipeState :: CompPipeline PipeState
- getPipeEnv :: CompPipeline PipeEnv
- hscPostBackendPhase :: DynFlags -> HscSource -> HscTarget -> Phase
- getLocation :: HscSource -> ModuleName -> CompPipeline ModLocation
- setModLocation :: ModLocation -> CompPipeline ()
- setDynFlags :: DynFlags -> CompPipeline ()
- runPhase :: PhasePlus -> FilePath -> DynFlags -> CompPipeline (PhasePlus, FilePath)
- exeFileName :: Bool -> DynFlags -> FilePath
- mkExtraObjToLinkIntoBinary :: DynFlags -> IO FilePath
- mkNoteObjsToLinkIntoBinary :: DynFlags -> [PackageId] -> IO [FilePath]
- maybeCreateManifest :: DynFlags -> FilePath -> IO [FilePath]
- runPhase_MoveBinary :: DynFlags -> FilePath -> IO Bool
- linkingNeeded :: DynFlags -> Bool -> [Linkable] -> [PackageId] -> IO Bool
- checkLinkInfo :: DynFlags -> [PackageId] -> FilePath -> IO Bool
Documentation
Just preprocess a file, put the result in a temp. file (used by the compilation manager during the summary phase).
We return the augmented DynFlags, because they contain the result of slurping in the OPTIONS pragmas
:: HscEnv | |
-> ModSummary | summary for module being compiled |
-> Int | module N ... |
-> Int | ... of M |
-> Maybe ModIface | old interface, if we have one |
-> Maybe Linkable | old linkable, if we have one |
-> SourceModified | |
-> IO HomeModInfo | the complete HomeModInfo, if successful |
Compile
Compile a single module, under the control of the compilation manager.
This is the interface between the compilation manager and the compiler proper (hsc), where we deal with tedious details like reading the OPTIONS pragma from the source file, converting the C or assembly that GHC produces into an object file, and compiling FFI stub files.
NB. No old interface can also mean that the source has changed.
:: Maybe TcGblEnv | |
-> Maybe Messager | |
-> HscEnv | |
-> ModSummary | summary for module being compiled |
-> Int | module N ... |
-> Int | ... of M |
-> Maybe ModIface | old interface, if we have one |
-> Maybe Linkable | old linkable, if we have one |
-> SourceModified | |
-> IO HomeModInfo | the complete HomeModInfo, if successful |
link :: GhcLink -> DynFlags -> Bool -> HomePackageTable -> IO SuccessFlag Source
newtype CompPipeline a Source
PipeEnv | |
|
PipeState | |
|
hscPostBackendPhase :: DynFlags -> HscSource -> HscTarget -> Phase Source
What phase to run after one of the backend code generators has run
setModLocation :: ModLocation -> CompPipeline () Source
setDynFlags :: DynFlags -> CompPipeline () Source
:: PhasePlus | Run this phase |
-> FilePath | name of the input file |
-> DynFlags | for convenience, we pass the current dflags in |
-> CompPipeline (PhasePlus, FilePath) |
Each phase in the pipeline returns the next phase to execute, and the name of the file in which the output was placed.
We must do things dynamically this way, because we often don't know what the rest of the phases will be until part-way through the compilation: for example, an {--} at the beginning of a source file can change the latter stages of the pipeline from taking the LLVM route to using the native code generator.
exeFileName :: Bool -> DynFlags -> FilePath Source