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

Safe HaskellNone
LanguageHaskell98

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

Pretty err => ErrorLoad !err

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

Pretty err => ErrorLint !err

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

Pretty (err (AnTEC SourcePos Name)) => ErrorSaltLoad (Error Name err) 
Pretty err => ErrorSaltConvert !err

Error converting the module to Salt to Sea.

Pretty err => ErrorTetraConvert !err

Error converting the module from Tetra to Salt.

Pretty err => ErrorFlowConvert !err

Error converting the module from Tetra to Salt.

Pretty err => ErrorCoreTransform !err

Error when transforming core program.

Instances

Pretty Error Source # 

Associated Types

data PrettyMode Error :: * #

Methods

pprDefaultMode :: PrettyMode Error #

ppr :: Error -> Doc #

pprPrec :: Int -> Error -> Doc #

pprModePrec :: PrettyMode Error -> Int -> Error -> Doc #

NFData Error Source # 

Methods

rnf :: Error -> () #

Source code

data PipeText n err where Source #

Process program text.

Constructors

PipeTextOutput :: !Sink -> PipeText n err 
PipeTextLoadCore :: (Ord n, Show n, Pretty n, Pretty (err (AnTEC SourcePos n))) => !(Fragment n err) -> !(Mode n) -> !Sink -> ![PipeCore (AnTEC SourcePos n) n] -> PipeText n err 
PipeTextLoadSourceTetra :: !Sink -> !Sink -> !Sink -> !Sink -> !Sink -> !Sink -> !Sink -> !Sink -> !Sink -> !Sink -> !Sink -> !Store -> ![PipeCore (AnTEC SourcePos Name) Name] -> 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 where Source #

Process a core module.

Constructors

PipeCoreId :: ![PipeCore a n] -> PipeCore a n 
PipeCoreOutput :: !(PrettyMode (Module a n)) -> !Sink -> PipeCore a n 
PipeCoreCheck :: (Pretty a, Pretty (err (AnTEC a n))) => !(Fragment n err) -> !(Mode n) -> !Sink -> ![PipeCore (AnTEC a n) n] -> PipeCore a n 
PipeCoreReCheck :: (NFData a, Show a, Pretty a, Pretty (err (AnTEC a n))) => !(Fragment n err) -> !(Mode n) -> ![PipeCore (AnTEC a n) n] -> PipeCore (AnTEC a n') n 
PipeCoreReannotate :: (NFData b, Show b) => (a -> b) -> ![PipeCore b n] -> PipeCore a n 
PipeCoreSimplify :: (Pretty a, CompoundName n) => !(Fragment n err) -> !s -> !(Simplifier s a n) -> ![PipeCore () n] -> PipeCore a n 
PipeCoreAsTetra :: ![PipeTetra a] -> PipeCore a Name 
PipeCoreAsFlow :: Pretty a => ![PipeFlow a] -> PipeCore a Name 
PipeCoreAsSalt :: Pretty a => ![PipeSalt a] -> PipeCore a Name 
PipeCoreHacks :: (NFData a, Show b, NFData b) => Canned (Module a n -> IO (Module b n)) -> ![PipeCore b n] -> PipeCore a n 

pipeCore :: (NFData a, Show a, NFData 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 Tetra modules

data PipeTetra a where Source #

Process a Core Tetra module.

Constructors

PipeTetraOutput :: !Sink -> PipeTetra a 
PipeTetraCurry :: (NFData a, Show a) => !Sink -> ![PipeCore () Name] -> PipeTetra (AnTEC a Name) 
PipeTetraBoxing :: (NFData a, Show a) => ![PipeCore a Name] -> PipeTetra a 
PipeTetraToSalt :: (NFData a, Show a) => !Platform -> !Config -> ![PipeCore a Name] -> PipeTetra (AnTEC a Name) 
PipeTetraToPHP :: (NFData a, Show a) => !Sink -> PipeTetra a 

pipeTetra :: Module a Name -> PipeTetra a -> IO [Error] Source #

Process a Core Tetra module.

Core Flow modules

data PipeFlow a where Source #

Process a Core Flow module.

pipeFlow :: Module a Name -> PipeFlow a -> IO [Error] Source #

Process a Core Flow module.

Core Salt modules

data PipeSalt a where Source #

Process a Core Salt module.

Instances

Show a => Show (PipeSalt a) Source # 

Methods

showsPrec :: Int -> PipeSalt a -> ShowS #

show :: PipeSalt a -> String #

showList :: [PipeSalt a] -> ShowS #

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.