raw-feldspar-0.1: Resource-Aware Feldspar

Safe HaskellNone
LanguageHaskell2010

Feldspar.Run.Compile

Contents

Synopsis

Struct expressions and variables

type VExp = Struct PrimType' Prim Source #

Struct expression

data VExp' where Source #

Struct expression with hidden result type

Constructors

VExp' :: Struct PrimType' Prim a -> VExp' 

Compilation options

data CompilerOpts Source #

Options affecting code generation

A default set of options is given by def.

The assertion labels to include in the generated code can be stated using the functions select, allExcept and selectBy. For example

def {compilerAssertions = allExcept [InternalAssertion]}

states that we want to include all except internal assertions.

Constructors

CompilerOpts 

Fields

Translation environment

data Env Source #

Translation environment

Constructors

Env 

Instances

(:<:) (* -> *, (* -> *, (* -> Constraint, *))) * ControlCMD instr => Reexpressible * (* -> Constraint, *) (AssertCMD (* -> *) (* -> Constraint)) instr Env Source # 

Methods

reexpressInstrEnv :: Monad m => (forall b. exp1 b -> ReaderT * env (ProgramT (AssertCMD (* -> *) (* -> Constraint) -> *, instr) instr ((AssertCMD (* -> *) (* -> Constraint) -> *, instr) exp2 fs) m) (exp2 b)) -> Env ((* -> *, (AssertCMD (* -> *) (* -> Constraint) -> *, instr)) (ReaderT * env (ProgramT (AssertCMD (* -> *) (* -> Constraint) -> *, instr) instr ((AssertCMD (* -> *) (* -> Constraint) -> *, instr) exp2 fs) m)) ((AssertCMD (* -> *) (* -> Constraint) -> *, instr) exp1 fs)) a -> ReaderT * env (ProgramT (AssertCMD (* -> *) (* -> Constraint) -> *, instr) instr ((AssertCMD (* -> *) (* -> Constraint) -> *, instr) exp2 fs) m) a #

localAlias Source #

Arguments

:: MonadReader Env m 
=> Name

Old name

-> VExp a

New expression

-> m b 
-> m b 

Add a local alias to the environment

lookAlias :: MonadReader Env m => TypeRep a -> Name -> m (VExp a) Source #

Lookup an alias in the environment

Translation of expressions

type TargetT m = ReaderT Env (ProgramT TargetCMD (Param2 Prim PrimType') m) Source #

Target monad during translation

type ProgC = Program TargetCMD (Param2 Prim PrimType') Source #

Monad for translated program

translateExp :: forall m a. Monad m => Data a -> TargetT m (VExp a) Source #

Translate an expression

unsafeTransSmallExp :: Monad m => Data a -> TargetT m (Prim a) Source #

Translate an expression that is assumed to fulfill PrimType a

translate :: Env -> Run a -> ProgC a Source #

Back ends

runIO :: MonadRun m => m a -> IO a Source #

Interpret a program in the IO monad

runIO' :: MonadRun m => m a -> IO a Source #

Interpret a program in the IO monad

captureIO Source #

Arguments

:: MonadRun m 
=> m a

Program to run

-> String

Input to send to stdin

-> IO String

Result from stdout

Like runIO but with explicit inputoutput connected to stdinstdout

compile' :: MonadRun m => CompilerOpts -> m a -> String Source #

Compile a program to C code represented as a string. To compile the resulting C code, use something like

cc -std=c99 YOURPROGRAM.c

This function returns only the first (main) module. To get all C translation unit, use compileAll.

compile :: MonadRun m => m a -> String Source #

Compile a program to C code represented as a string. To compile the resulting C code, use something like

cc -std=c99 YOURPROGRAM.c

This function returns only the first (main) module. To get all C translation unit, use compileAll.

By default, only assertions labeled with UserAssertion will be included in the generated code.

compileAll' :: MonadRun m => CompilerOpts -> m a -> [(String, String)] Source #

Compile a program to C modules, each one represented as a pair of a name and the code represented as a string

To compile the resulting C code, use something like

cc -std=c99 YOURPROGRAM.c

compileAll :: MonadRun m => m a -> [(String, String)] Source #

Compile a program to C modules, each one represented as a pair of a name and the code represented as a string

To compile the resulting C code, use something like

cc -std=c99 YOURPROGRAM.c

By default, only assertions labeled with UserAssertion will be included in the generated code.

icompile' :: MonadRun m => CompilerOpts -> m a -> IO () Source #

Compile a program to C code and print it on the screen. To compile the resulting C code, use something like

cc -std=c99 YOURPROGRAM.c

icompile :: MonadRun m => m a -> IO () Source #

Compile a program to C code and print it on the screen. To compile the resulting C code, use something like

cc -std=c99 YOURPROGRAM.c

By default, only assertions labeled with UserAssertion will be included in the generated code.

compileAndCheck' :: MonadRun m => CompilerOpts -> ExternalCompilerOpts -> m a -> IO () Source #

Generate C code and use CC to check that it compiles (no linking)

compileAndCheck :: MonadRun m => m a -> IO () Source #

Generate C code and use CC to check that it compiles (no linking)

By default, all assertions will be included in the generated code.

runCompiled' :: MonadRun m => CompilerOpts -> ExternalCompilerOpts -> m a -> IO () Source #

Generate C code, use CC to compile it, and run the resulting executable

runCompiled :: MonadRun m => m a -> IO () Source #

Generate C code, use CC to compile it, and run the resulting executable

By default, all assertions will be included in the generated code.

withCompiled' Source #

Arguments

:: MonadRun m 
=> CompilerOpts 
-> ExternalCompilerOpts 
-> m a

Program to compile

-> ((String -> IO String) -> IO b)

Function that has access to the compiled executable as a function

-> IO b 

Compile a program and make it available as an IO function from String to String (connected to stdin/stdout. respectively). Note that compilation only happens once, even if the IO function is used many times in the body.

withCompiled Source #

Arguments

:: MonadRun m 
=> m a

Program to compile

-> ((String -> IO String) -> IO b)

Function that has access to the compiled executable as a function

-> IO b 

Compile a program and make it available as an IO function from String to String (connected to stdin/stdout. respectively). Note that compilation only happens once, even if the IO function is used many times in the body.

By default, all assertions will be included in the generated code.

captureCompiled' Source #

Arguments

:: MonadRun m 
=> CompilerOpts 
-> ExternalCompilerOpts 
-> m a

Program to run

-> String

Input to send to stdin

-> IO String

Result from stdout

Like runCompiled' but with explicit input/output connected to stdin/stdout. Note that the program will be compiled every time the function is applied to a string. In order to compile once and run many times, use the function withCompiled'.

captureCompiled Source #

Arguments

:: MonadRun m 
=> m a

Program to run

-> String

Input to send to stdin

-> IO String

Result from stdout

Like runCompiled but with explicit input/output connected to stdin/stdout. Note that the program will be compiled every time the function is applied to a string. In order to compile once and run many times, use the function withCompiled.

By default, all assertions will be included in the generated code.

compareCompiled' Source #

Arguments

:: MonadRun m 
=> CompilerOpts 
-> ExternalCompilerOpts 
-> m a

Program to run

-> IO a

Reference program

-> String

Input to send to stdin

-> IO () 

Compare the content written to stdout from the reference program and from running the compiled C code

compareCompiled Source #

Arguments

:: MonadRun m 
=> m a

Program to run

-> IO a

Reference program

-> String

Input to send to stdin

-> IO () 

Compare the content written to stdout from the reference program and from running the compiled C code

By default, all assertions will be included in the generated code.