Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Futhark.Pipeline
Description
Definition of the core compiler driver building blocks. The
spine of the compiler is the FutharkM
monad, although note that
individual passes are pure functions, and do not use the FutharkM
monad (see Futhark.Pass).
Running the compiler involves producing an initial IR program (see
Futhark.Compiler.Program), running a Pipeline
to produce a
final program (still in IR), then running an Action
, which is
usually a code generator.
Synopsis
- data Pipeline fromrep torep
- data PipelineConfig = PipelineConfig {}
- data Action rep = Action {
- actionName :: String
- actionDescription :: String
- actionProcedure :: Prog rep -> FutharkM ()
- data FutharkM a
- runFutharkM :: FutharkM a -> Verbosity -> IO (Either CompilerError a)
- data Verbosity
- module Futhark.Error
- onePass :: Checkable torep => Pass fromrep torep -> Pipeline fromrep torep
- passes :: Checkable rep => [Pass rep rep] -> Pipeline rep rep
- condPipeline :: (Prog rep -> Bool) -> Pipeline rep rep -> Pipeline rep rep
- runPipeline :: Pipeline fromrep torep -> PipelineConfig -> Prog fromrep -> FutharkM (Prog torep)
Documentation
data Pipeline fromrep torep Source #
A compiler pipeline is conceptually a function from programs to
programs, where the actual representation may change. Pipelines
can be composed using their Category
instance.
data PipelineConfig Source #
Configuration object for running a compiler pipeline.
Constructors
PipelineConfig | |
Fields |
A compilation always ends with some kind of action.
Constructors
Action | |
Fields
|
The main Futhark compiler driver monad - basically some state
tracking on top if IO
.
Instances
MonadIO FutharkM Source # | |
Defined in Futhark.Pipeline | |
Applicative FutharkM Source # | |
Functor FutharkM Source # | |
Monad FutharkM Source # | |
MonadFreshNames FutharkM Source # | |
Defined in Futhark.Pipeline Methods getNameSource :: FutharkM VNameSource Source # putNameSource :: VNameSource -> FutharkM () Source # | |
MonadLogger FutharkM Source # | |
MonadError CompilerError FutharkM Source # | |
Defined in Futhark.Pipeline Methods throwError :: CompilerError -> FutharkM a # catchError :: FutharkM a -> (CompilerError -> FutharkM a) -> FutharkM a # |
runFutharkM :: FutharkM a -> Verbosity -> IO (Either CompilerError a) Source #
Run a FutharkM
action.
How much information to print to stderr while the compiler is running.
Constructors
NotVerbose | Silence is golden. |
Verbose | Print messages about which pass is running. |
VeryVerbose | Also print logs from individual passes. |
Instances
Eq Verbosity Source # | |
Ord Verbosity Source # | |
module Futhark.Error
onePass :: Checkable torep => Pass fromrep torep -> Pipeline fromrep torep Source #
Construct a pipeline from a single compiler pass.
passes :: Checkable rep => [Pass rep rep] -> Pipeline rep rep Source #
Create a pipeline from a list of passes.
condPipeline :: (Prog rep -> Bool) -> Pipeline rep rep -> Pipeline rep rep Source #
Conditionally run pipeline if predicate is true.
runPipeline :: Pipeline fromrep torep -> PipelineConfig -> Prog fromrep -> FutharkM (Prog torep) Source #
Run the pipeline on the given program.