ghc-lib-9.4.4.20221225: The GHC API, decoupled from GHC versions
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Driver.Pipeline

Synopsis

Run a series of compilation steps in a pipeline, for a

Interfaces for the compilation manager (interpreted/batch-mode)

preprocess Source #

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

compileOne Source #

Arguments

:: 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

-> 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.

compileOne' Source #

Arguments

:: 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

-> IO HomeModInfo

the complete HomeModInfo, if successful

Linking

link Source #

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 

PipeEnv

data PipeEnv #

Constructors

PipeEnv 

Fields

phaseOutputFilenameNew Source #

Arguments

:: Phase

The next phase

-> PipeEnv 
-> HscEnv 
-> Maybe ModLocation

A ModLocation, if we are compiling a Haskell source file

-> IO FilePath 

Running individual phases

runPhase :: TPhase out -> IO out Source #

Default interpretation of each phase, in terms of IO.

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) #

class MonadUse (f :: Type -> Type) (m :: Type -> Type) where #

Lift a f action into an m action.

Methods

use :: f a -> m a #

Instances

Instances details
MonadUse TPhase HookedUse Source # 
Instance details

Defined in GHC.Driver.Pipeline.Execute

Methods

use :: TPhase a -> HookedUse a #

preprocessPipeline :: P m => PipeEnv -> HscEnv -> FilePath -> m (DynFlags, FilePath) Source #

The preprocessor pipeline

fullPipeline :: P m => PipeEnv -> HscEnv -> FilePath -> HscSource -> m (ModIface, Maybe Linkable) Source #

The complete compilation pipeline, from start to finish

hscPipeline :: P m => PipeEnv -> (HscEnv, ModSummary, HscRecompStatus) -> m (ModIface, Maybe Linkable) Source #

Everything after preprocess

Default method of running a pipeline

runPipeline :: Hooks -> HookedUse a -> IO a Source #

The default mechanism to run a pipeline, see Note [The Pipeline Monad]