| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GHC.Driver.Pipeline.Execute
Synopsis
- newtype HookedUse a = HookedUse {
- runHookedUse :: (Hooks, PhaseHook) -> IO a
 
 - runPipeline :: Hooks -> HookedUse a -> IO a
 - runPhase :: TPhase out -> IO out
 - runLlvmManglePhase :: PipeEnv -> HscEnv -> FilePath -> IO [Char]
 - runMergeForeign :: PipeEnv -> HscEnv -> FilePath -> [FilePath] -> IO FilePath
 - runLlvmLlcPhase :: PipeEnv -> HscEnv -> FilePath -> IO FilePath
 - runLlvmOptPhase :: PipeEnv -> HscEnv -> FilePath -> IO FilePath
 - runAsPhase :: Bool -> PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> IO FilePath
 - runJsPhase :: PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> IO FilePath
 - runForeignJsPhase :: PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> IO FilePath
 - applyAssemblerProg :: DefunctionalizedAssemblerProg -> Logger -> DynFlags -> Platform -> [Option] -> IO ()
 - runCcPhase :: Phase -> PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> IO FilePath
 - runHscBackendPhase :: PipeEnv -> HscEnv -> ModuleName -> HscSource -> ModLocation -> HscBackendAction -> IO ([FilePath], ModIface, HomeModLinkable, FilePath)
 - runUnlitPhase :: HscEnv -> FilePath -> FilePath -> IO FilePath
 - getFileArgs :: HscEnv -> FilePath -> IO (DynFlags, Messages PsMessage, Messages DriverMessage)
 - runCppPhase :: HscEnv -> FilePath -> FilePath -> IO FilePath
 - runHscPhase :: PipeEnv -> HscEnv -> FilePath -> HscSource -> IO (HscEnv, ModSummary, HscRecompStatus)
 - mkOneShotModLocation :: PipeEnv -> DynFlags -> HscSource -> ModuleName -> IO ModLocation
 - runHscTcPhase :: HscEnv -> ModSummary -> IO (FrontendResult, Messages GhcMessage)
 - runHscPostTcPhase :: HscEnv -> ModSummary -> FrontendResult -> Messages GhcMessage -> Maybe Fingerprint -> IO HscBackendAction
 - runHsPpPhase :: HscEnv -> FilePath -> FilePath -> FilePath -> IO FilePath
 - phaseOutputFilenameNew :: Phase -> PipeEnv -> HscEnv -> Maybe ModLocation -> IO FilePath
 - getOutputFilename :: Logger -> TmpFs -> Phase -> PipelineOutput -> String -> DynFlags -> Phase -> Maybe ModLocation -> IO FilePath
 - llvmOptions :: LlvmConfig -> DynFlags -> [(String, String)]
 - hscPostBackendPhase :: HscSource -> Backend -> Phase
 - compileStub :: HscEnv -> FilePath -> IO FilePath
 - joinObjectFiles :: HscEnv -> [FilePath] -> FilePath -> IO ()
 - getHCFilePackages :: FilePath -> IO [UnitId]
 - linkDynLibCheck :: Logger -> TmpFs -> DynFlags -> UnitEnv -> [String] -> [UnitId] -> IO ()
 - touchObjectFile :: Logger -> DynFlags -> FilePath -> IO ()
 
Documentation
Constructors
| HookedUse | |
Fields 
  | |
Instances
runPipeline :: Hooks -> HookedUse a -> IO a Source #
The default mechanism to run a pipeline, see Note [The Pipeline Monad]
runJsPhase :: PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> IO FilePath Source #
Run the JS Backend postHsc phase.
runForeignJsPhase :: PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> IO FilePath Source #
Deal with foreign JS files (embed them into .o files)
applyAssemblerProg :: DefunctionalizedAssemblerProg -> Logger -> DynFlags -> Platform -> [Option] -> IO () Source #
runHscBackendPhase :: PipeEnv -> HscEnv -> ModuleName -> HscSource -> ModLocation -> HscBackendAction -> IO ([FilePath], ModIface, HomeModLinkable, FilePath) Source #
getFileArgs :: HscEnv -> FilePath -> IO (DynFlags, Messages PsMessage, Messages DriverMessage) Source #
runHscPhase :: PipeEnv -> HscEnv -> FilePath -> HscSource -> IO (HscEnv, ModSummary, HscRecompStatus) Source #
mkOneShotModLocation :: PipeEnv -> DynFlags -> HscSource -> ModuleName -> IO ModLocation Source #
Calculate the ModLocation from the provided DynFlags. This function is only used in one-shot mode and therefore takes into account the effect of -o/-ohi flags (which do nothing in --make mode)
runHscTcPhase :: HscEnv -> ModSummary -> IO (FrontendResult, Messages GhcMessage) Source #
runHscPostTcPhase :: HscEnv -> ModSummary -> FrontendResult -> Messages GhcMessage -> Maybe Fingerprint -> IO HscBackendAction Source #
getOutputFilename :: Logger -> TmpFs -> Phase -> PipelineOutput -> String -> DynFlags -> Phase -> Maybe ModLocation -> IO FilePath Source #
Computes the next output filename for something in the compilation pipeline. This is controlled by several variables:
Phase: the last phase to be run (e.g.stopPhase). This is used to tell if we're in the last phase or not, because in that case flags like-omay be important.PipelineOutput: is this intended to be aTemporaryorPersistentbuild output? Temporary files just go in a fresh temporary name.String: what was the basename of the original input file?DynFlags: the obvious thingPhase: the phase we want to determine the output filename of.Maybe ModLocation: theModLocationof the module we're compiling; this can be used to override the default output of an object file. (TODO: do we actually need this?)
Arguments
| :: LlvmConfig | |
| -> DynFlags | |
| -> [(String, String)] | pairs of (opt, llc) arguments  | 
LLVM Options. These are flags to be passed to opt and llc, to ensure consistency we list them in pairs, so that they form groups.