| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
GHC.Driver.Pipeline
Synopsis
- oneShot :: HscEnv -> StopPhase -> [(String, Maybe Phase)] -> IO ()
- compileFile :: HscEnv -> StopPhase -> (FilePath, Maybe Phase) -> IO (Maybe FilePath)
- preprocess :: HscEnv -> FilePath -> Maybe InputFileBuffer -> Maybe Phase -> IO (Either DriverMessages (DynFlags, FilePath))
- compileOne :: HscEnv -> ModSummary -> Int -> Int -> Maybe ModIface -> HomeModLinkable -> IO HomeModInfo
- compileOne' :: Maybe Messager -> HscEnv -> ModSummary -> Int -> Int -> Maybe ModIface -> HomeModLinkable -> IO HomeModInfo
- compileForeign :: HscEnv -> ForeignSrcLang -> FilePath -> IO FilePath
- compileEmptyStub :: DynFlags -> HscEnv -> FilePath -> ModLocation -> ModuleName -> IO ()
- link :: GhcLink -> Logger -> TmpFs -> Hooks -> DynFlags -> UnitEnv -> Bool -> Maybe (RecompileRequired -> IO ()) -> HomePackageTable -> IO SuccessFlag
- linkingNeeded :: Logger -> DynFlags -> UnitEnv -> Bool -> [Linkable] -> [UnitId] -> IO RecompileRequired
- checkLinkInfo :: Logger -> DynFlags -> UnitEnv -> [UnitId] -> FilePath -> IO Bool
- data PipeEnv = PipeEnv {}
- mkPipeEnv :: StopPhase -> FilePath -> Maybe Phase -> PipelineOutput -> PipeEnv
- phaseOutputFilenameNew :: Phase -> PipeEnv -> HscEnv -> Maybe ModLocation -> IO FilePath
- data TPhase res where- T_Unlit :: PipeEnv -> HscEnv -> FilePath -> TPhase [Char]
- T_FileArgs :: HscEnv -> FilePath -> TPhase (DynFlags, Messages PsMessage, [Warn])
- T_Cpp :: PipeEnv -> HscEnv -> FilePath -> TPhase [Char]
- T_HsPp :: PipeEnv -> HscEnv -> FilePath -> FilePath -> TPhase [Char]
- T_HscRecomp :: PipeEnv -> HscEnv -> FilePath -> HscSource -> TPhase (HscEnv, ModSummary, HscRecompStatus)
- T_Hsc :: HscEnv -> ModSummary -> TPhase (FrontendResult, Messages GhcMessage)
- T_HscPostTc :: HscEnv -> ModSummary -> FrontendResult -> Messages GhcMessage -> Maybe Fingerprint -> TPhase HscBackendAction
- T_HscBackend :: PipeEnv -> HscEnv -> ModuleName -> HscSource -> ModLocation -> HscBackendAction -> TPhase ([FilePath], ModIface, HomeModLinkable, FilePath)
- T_CmmCpp :: PipeEnv -> HscEnv -> FilePath -> TPhase [Char]
- T_Cmm :: PipeEnv -> HscEnv -> FilePath -> TPhase ([FilePath], FilePath)
- T_Cc :: Phase -> PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> TPhase [Char]
- T_As :: Bool -> PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> TPhase [Char]
- T_Js :: PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> TPhase [Char]
- T_LlvmOpt :: PipeEnv -> HscEnv -> FilePath -> TPhase [Char]
- T_LlvmLlc :: PipeEnv -> HscEnv -> FilePath -> TPhase [Char]
- T_LlvmMangle :: PipeEnv -> HscEnv -> FilePath -> TPhase [Char]
- T_MergeForeign :: PipeEnv -> HscEnv -> FilePath -> [FilePath] -> TPhase [Char]
 
- runPhase :: TPhase out -> IO out
- hscPostBackendPhase :: HscSource -> Backend -> Phase
- type TPipelineClass (f :: Type -> Type) (m :: Type -> Type) = (Functor m, MonadIO m, Applicative m, Monad m, MonadUse f m)
- class MonadUse (f :: Type -> Type) (m :: Type -> Type) where- use :: f a -> m a
 
- preprocessPipeline :: P m => PipeEnv -> HscEnv -> FilePath -> m (DynFlags, FilePath)
- fullPipeline :: P m => PipeEnv -> HscEnv -> FilePath -> HscSource -> m (ModIface, HomeModLinkable)
- hscPipeline :: P m => PipeEnv -> (HscEnv, ModSummary, HscRecompStatus) -> m (ModIface, HomeModLinkable)
- hscBackendPipeline :: P m => PipeEnv -> HscEnv -> ModSummary -> HscBackendAction -> m (ModIface, HomeModLinkable)
- hscPostBackendPipeline :: P m => PipeEnv -> HscEnv -> HscSource -> Backend -> Maybe ModLocation -> FilePath -> m (Maybe FilePath)
- hscGenBackendPipeline :: P m => PipeEnv -> HscEnv -> ModSummary -> HscBackendAction -> m (ModIface, HomeModLinkable)
- asPipeline :: P m => Bool -> PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> m (Maybe ObjFile)
- viaCPipeline :: P m => Phase -> PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> m (Maybe FilePath)
- cmmCppPipeline :: P m => PipeEnv -> HscEnv -> FilePath -> m FilePath
- cmmPipeline :: P m => PipeEnv -> HscEnv -> FilePath -> m FilePath
- jsPipeline :: P m => PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> m FilePath
- llvmPipeline :: P m => PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> m (Maybe FilePath)
- llvmLlcPipeline :: P m => PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> m (Maybe FilePath)
- llvmManglePipeline :: P m => PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> m (Maybe FilePath)
- pipelineStart :: P m => PipeEnv -> HscEnv -> FilePath -> Maybe Phase -> m (Maybe FilePath)
- runPipeline :: Hooks -> HookedUse a -> IO a
Run a series of compilation steps in a pipeline, for a
Interfaces for the compilation manager (interpreted/batch-mode)
Arguments
| :: HscEnv | |
| -> FilePath | input filename | 
| -> Maybe InputFileBuffer | optional buffer to use instead of reading the input file | 
| -> Maybe Phase | starting phase | 
| -> IO (Either DriverMessages (DynFlags, FilePath)) | 
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
Arguments
| :: HscEnv | |
| -> ModSummary | summary for module being compiled | 
| -> Int | module N ... | 
| -> Int | ... of M | 
| -> Maybe ModIface | old interface, if we have one | 
| -> HomeModLinkable | old linkable, if we have one | 
| -> 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.
Arguments
| :: Maybe Messager | |
| -> HscEnv | |
| -> ModSummary | summary for module being compiled | 
| -> Int | module N ... | 
| -> Int | ... of M | 
| -> Maybe ModIface | old interface, if we have one | 
| -> HomeModLinkable | |
| -> IO HomeModInfo | the complete HomeModInfo, if successful | 
compileForeign :: HscEnv -> ForeignSrcLang -> FilePath -> IO FilePath Source #
compileEmptyStub :: DynFlags -> HscEnv -> FilePath -> ModLocation -> ModuleName -> IO () Source #
Linking
Arguments
| :: GhcLink | interactive or batch | 
| -> Logger | Logger | 
| -> TmpFs | |
| -> Hooks | |
| -> DynFlags | dynamic flags | 
| -> UnitEnv | unit environment | 
| -> Bool | attempt linking in batch mode? | 
| -> Maybe (RecompileRequired -> IO ()) | |
| -> HomePackageTable | what to link | 
| -> IO SuccessFlag | 
linkingNeeded :: Logger -> DynFlags -> UnitEnv -> Bool -> [Linkable] -> [UnitId] -> IO RecompileRequired Source #
PipeEnv
Constructors
| PipeEnv | |
| Fields 
 | |
Running individual phases
Constructors
hscPostBackendPhase :: HscSource -> Backend -> Phase Source #
What phase to run after one of the backend code generators has run
Constructing Pipelines
type TPipelineClass (f :: Type -> Type) (m :: Type -> Type) = (Functor m, MonadIO m, Applicative m, Monad m, MonadUse f m) #
preprocessPipeline :: P m => PipeEnv -> HscEnv -> FilePath -> m (DynFlags, FilePath) Source #
The preprocessor pipeline
fullPipeline :: P m => PipeEnv -> HscEnv -> FilePath -> HscSource -> m (ModIface, HomeModLinkable) Source #
The complete compilation pipeline, from start to finish
hscPipeline :: P m => PipeEnv -> (HscEnv, ModSummary, HscRecompStatus) -> m (ModIface, HomeModLinkable) Source #
Everything after preprocess
hscBackendPipeline :: P m => PipeEnv -> HscEnv -> ModSummary -> HscBackendAction -> m (ModIface, HomeModLinkable) Source #
hscPostBackendPipeline :: P m => PipeEnv -> HscEnv -> HscSource -> Backend -> Maybe ModLocation -> FilePath -> m (Maybe FilePath) Source #
hscGenBackendPipeline :: P m => PipeEnv -> HscEnv -> ModSummary -> HscBackendAction -> m (ModIface, HomeModLinkable) Source #
asPipeline :: P m => Bool -> PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> m (Maybe ObjFile) Source #
viaCPipeline :: P m => Phase -> PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> m (Maybe FilePath) Source #
jsPipeline :: P m => PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> m FilePath Source #
llvmPipeline :: P m => PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> m (Maybe FilePath) Source #
llvmLlcPipeline :: P m => PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> m (Maybe FilePath) Source #
llvmManglePipeline :: P m => PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> m (Maybe FilePath) Source #