futhark-0.21.11: An optimising compiler for a functional, array-oriented language.
Safe HaskellTrustworthy
LanguageHaskell2010

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

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.

Instances

Instances details
Category Pipeline Source # 
Instance details

Defined in Futhark.Pipeline

Methods

id :: forall (a :: k). Pipeline a a #

(.) :: forall (b :: k) (c :: k) (a :: k). Pipeline b c -> Pipeline a b -> Pipeline a c #

data PipelineConfig Source #

Configuration object for running a compiler pipeline.

data Action rep Source #

A compilation always ends with some kind of action.

Constructors

Action 

data FutharkM a Source #

The main Futhark compiler driver monad - basically some state tracking on top if IO.

Instances

Instances details
Monad FutharkM Source # 
Instance details

Defined in Futhark.Pipeline

Methods

(>>=) :: FutharkM a -> (a -> FutharkM b) -> FutharkM b #

(>>) :: FutharkM a -> FutharkM b -> FutharkM b #

return :: a -> FutharkM a #

Functor FutharkM Source # 
Instance details

Defined in Futhark.Pipeline

Methods

fmap :: (a -> b) -> FutharkM a -> FutharkM b #

(<$) :: a -> FutharkM b -> FutharkM a #

Applicative FutharkM Source # 
Instance details

Defined in Futhark.Pipeline

Methods

pure :: a -> FutharkM a #

(<*>) :: FutharkM (a -> b) -> FutharkM a -> FutharkM b #

liftA2 :: (a -> b -> c) -> FutharkM a -> FutharkM b -> FutharkM c #

(*>) :: FutharkM a -> FutharkM b -> FutharkM b #

(<*) :: FutharkM a -> FutharkM b -> FutharkM a #

MonadIO FutharkM Source # 
Instance details

Defined in Futhark.Pipeline

Methods

liftIO :: IO a -> FutharkM a #

MonadLogger FutharkM Source # 
Instance details

Defined in Futhark.Pipeline

Methods

logMsg :: ToLog a => a -> FutharkM () Source #

addLog :: Log -> FutharkM () Source #

MonadFreshNames FutharkM Source # 
Instance details

Defined in Futhark.Pipeline

MonadError CompilerError FutharkM Source # 
Instance details

Defined in Futhark.Pipeline

data Verbosity Source #

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.

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.