ddc-build-0.4.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

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.

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

Error converting the module to Salt to Sea.

forall err . Pretty err => ErrorTetraConvert !err

Error converting the module from Tetra to Salt.

forall err . Pretty err => ErrorLiteConvert !err

Error converting the module from Lite to Salt.

forall err . Pretty err => ErrorCoreTransform !err

Error when transforming core program.

Instances

Pretty Error 
NFData Error 

Source code

data PipeText n err whereSource

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 -> ![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 whereSource

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 :: !(Fragment n err) -> !s -> !(Simplifier s a n) -> ![PipeCore () n] -> PipeCore a n 
PipeCoreAsTetra :: ![PipeTetra (AnTEC a Name)] -> PipeCore (AnTEC a Name) Name 
PipeCoreAsLite :: ![PipeLite] -> PipeCore (AnTEC () Name) 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, 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 Tetra modules

data PipeTetra a whereSource

Process a Core Tetra module.

Constructors

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

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

Process a Core Tetra module.

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 Flow modules

data PipeFlow a whereSource

Process a Core Flow module.

Constructors

PipeFlowOutput :: Sink -> PipeFlow a 
PipeFlowHacks :: (NFData a, Show b, NFData b) => Canned (Module a Name -> IO (Module b Name)) -> ![PipeFlow b] -> PipeFlow a 
PipeFlowPrep :: [PipeCore () Name] -> PipeFlow () 
PipeFlowRate :: [PipeCore () Name] -> PipeFlow () 
PipeFlowLower :: Config -> [PipeCore () Name] -> PipeFlow (AnTEC () Name) 
PipeFlowMelt :: [PipeCore () Name] -> PipeFlow (AnTEC () Name) 
PipeFlowWind :: [PipeCore () Name] -> PipeFlow (AnTEC () Name) 

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

Process a Core Flow module.

Core Salt modules

data PipeSalt a whereSource

Process a Core Salt module.

Constructors

PipeSaltId :: ![PipeSalt a] -> PipeSalt a 
PipeSaltOutput :: !Sink -> PipeSalt a 
PipeSaltTransfer :: ![PipeSalt (AnTEC a Name)] -> PipeSalt (AnTEC a Name) 
PipeSaltPrint :: !Bool -> !Platform -> !Sink -> PipeSalt a 
PipeSaltToLlvm :: !Platform -> ![PipeLlvm] -> PipeSalt a 
PipeSaltCompile :: !Platform -> !Builder -> !FilePath -> !FilePath -> !(Maybe FilePath) -> !Bool -> PipeSalt a 

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

data PipeLlvm Source

Process an LLVM module.

Constructors

PipeLlvmPrint Sink 
PipeLlvmCompile 

Fields

pipeBuilder :: Builder
 
pipeFileLlvm :: FilePath
 
pipeFileAsm :: FilePath
 
pipeFileObject :: FilePath
 
pipeFileExe :: Maybe FilePath
 
pipeKeepLlvmFiles :: Bool
 
pipeKeepAsmFiles :: Bool
 

Instances

Show PipeLlvm 

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

Show Sink 

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

Emit a string to the given Sink.