ddc-build-0.3.1.3: Disciplined Disciple Compiler build framework.

Safe HaskellNone

DDC.Build.Pipeline

Contents

Description

A pipeline is an abstraction of a single compiler pass.

NOTE: The Haddock documentation on pipeline constructors is missing because Haddock does not support commenting GADTs. See the source code for documentation.

Synopsis

Errors

data Error Source

Constructors

ErrorSaltLoad (Error Name) 
forall err . Pretty err => ErrorSaltConvert !err

Error converting the module to Disciple Core Salt.

forall err . Pretty err => ErrorLiteConvert !err

Error converting the module to Disciple Core Lite.

forall err . Pretty err => ErrorLoad !err

Error when loading a module. Blame it on the user.

forall err . Pretty err => ErrorLint !err

Error when type checking a transformed module. Blame it on the compiler.

Instances

Source code

data PipeText n err whereSource

Process program text.

Constructors

PipeTextOutput :: !Sink -> PipeText n err 
PipeTextLoadCore :: (Ord n, Show n, Pretty n) => !(Fragment n err) -> ![PipeCore (AnTEC () n) n] -> PipeText n err 

pipeText :: NFData n => String -> Int -> String -> PipeText n err -> IO [Error]Source

Process a text module.

Returns empty list on success.

Generic Core modules

data PipeCore a n whereSource

Process a core module.

Constructors

PipeCoreId :: ![PipeCore a n] -> PipeCore a n 
PipeCoreOutput :: !Sink -> PipeCore a n 
PipeCoreCheck :: !(Fragment n err) -> ![PipeCore (AnTEC a n) n] -> PipeCore a n 
PipeCoreReCheck :: (Show a, NFData a) => !(Fragment n err) -> ![PipeCore (AnTEC a n) n] -> PipeCore (AnTEC a n') n 
PipeCoreStrip :: ![PipeCore () n] -> PipeCore a n 
PipeCoreSimplify :: !(Fragment n err) -> !s -> !(Simplifier s a n) -> ![PipeCore () n] -> PipeCore a n 
PipeCoreAsLite :: ![PipeLite] -> PipeCore (AnTEC () Name) Name 
PipeCoreAsSalt :: Pretty a => ![PipeSalt a] -> PipeCore a Name 
PipeCoreHacks :: Canned (Module a n -> IO (Module a n)) -> ![PipeCore a n] -> PipeCore a n 

pipeCore :: (NFData a, Show a, NFData n, Eq n, Ord n, Show n, Pretty n) => Module a n -> PipeCore a n -> IO [Error]Source

Process a Core module.

Returns empty list on success.

Core Lite modules

data PipeLite Source

Process a Core Lite module.

Constructors

PipeLiteOutput !Sink

Output the module in core language syntax.

PipeLiteToSalt !Platform !Config ![PipeCore () Name]

Convert the module to the Core Salt Fragment.

pipeLite :: Module (AnTEC () Name) Name -> PipeLite -> IO [Error]Source

Process a Core Lite module.

Core Salt modules

data PipeSalt a whereSource

Process a Core Salt module.

Instances

Show a => Show (PipeSalt a) 

pipeSalt :: (Show a, Pretty a, NFData a) => Module a Name -> PipeSalt a -> IO [Error]Source

Process a Core Salt module.

Returns empty list on success.

LLVM modules

pipeLlvm :: Module -> PipeLlvm -> IO [Error]Source

Process an LLVM module.

Returns empty list on success.

Emitting output

data Sink Source

What to do with program text.

Constructors

SinkDiscard

Drop it on the floor.

SinkStdout

Emit it to stdout.

SinkFile FilePath

Write it to this file.

Instances

pipeSink :: String -> Sink -> IO [Error]Source

Emit a string to the given Sink.