raw-feldspar-0.4.1: Resource-Aware Feldspar
Safe HaskellNone
LanguageHaskell2010

Feldspar.Run

Description

Monad for running Feldspar programs and C code back ends

Synopsis

Front end

module Feldspar

Compilation options

data Selection a Source #

Selection: description of a set of values

Instances

Instances details
Semigroup (Selection a) Source # 
Instance details

Defined in Data.Selection

Methods

(<>) :: Selection a -> Selection a -> Selection a #

sconcat :: NonEmpty (Selection a) -> Selection a #

stimes :: Integral b => b -> Selection a -> Selection a #

Monoid (Selection a) Source #
mempty  = empty
mappend = union
Instance details

Defined in Data.Selection

select :: Eq a => [a] -> Selection a Source #

Create a classification from a list of elements

allExcept :: Eq a => [a] -> Selection a Source #

Select all values except those in the given list

selectBy :: (a -> Bool) -> Selection a Source #

Select the values that fulfill a predicate

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

Instances

Instances details
Default CompilerOpts Source # 
Instance details

Defined in Feldspar.Run.Compile

Methods

def :: CompilerOpts #

data ExternalCompilerOpts #

Constructors

ExternalCompilerOpts 

Fields

Instances

Instances details
Default ExternalCompilerOpts 
Instance details

Defined in Language.Embedded.Backend.C

class Default a where #

A class for types with a default value.

Minimal complete definition

Nothing

Methods

def :: a #

The default value for this type.

Instances

Instances details
Default Double 
Instance details

Defined in Data.Default.Class

Methods

def :: Double #

Default Float 
Instance details

Defined in Data.Default.Class

Methods

def :: Float #

Default Int 
Instance details

Defined in Data.Default.Class

Methods

def :: Int #

Default Int8 
Instance details

Defined in Data.Default.Class

Methods

def :: Int8 #

Default Int16 
Instance details

Defined in Data.Default.Class

Methods

def :: Int16 #

Default Int32 
Instance details

Defined in Data.Default.Class

Methods

def :: Int32 #

Default Int64 
Instance details

Defined in Data.Default.Class

Methods

def :: Int64 #

Default Integer 
Instance details

Defined in Data.Default.Class

Methods

def :: Integer #

Default Ordering 
Instance details

Defined in Data.Default.Class

Methods

def :: Ordering #

Default Word 
Instance details

Defined in Data.Default.Class

Methods

def :: Word #

Default Word8 
Instance details

Defined in Data.Default.Class

Methods

def :: Word8 #

Default Word16 
Instance details

Defined in Data.Default.Class

Methods

def :: Word16 #

Default Word32 
Instance details

Defined in Data.Default.Class

Methods

def :: Word32 #

Default Word64 
Instance details

Defined in Data.Default.Class

Methods

def :: Word64 #

Default () 
Instance details

Defined in Data.Default.Class

Methods

def :: () #

Default All 
Instance details

Defined in Data.Default.Class

Methods

def :: All #

Default Any 
Instance details

Defined in Data.Default.Class

Methods

def :: Any #

Default CShort 
Instance details

Defined in Data.Default.Class

Methods

def :: CShort #

Default CUShort 
Instance details

Defined in Data.Default.Class

Methods

def :: CUShort #

Default CInt 
Instance details

Defined in Data.Default.Class

Methods

def :: CInt #

Default CUInt 
Instance details

Defined in Data.Default.Class

Methods

def :: CUInt #

Default CLong 
Instance details

Defined in Data.Default.Class

Methods

def :: CLong #

Default CULong 
Instance details

Defined in Data.Default.Class

Methods

def :: CULong #

Default CLLong 
Instance details

Defined in Data.Default.Class

Methods

def :: CLLong #

Default CULLong 
Instance details

Defined in Data.Default.Class

Methods

def :: CULLong #

Default CFloat 
Instance details

Defined in Data.Default.Class

Methods

def :: CFloat #

Default CDouble 
Instance details

Defined in Data.Default.Class

Methods

def :: CDouble #

Default CPtrdiff 
Instance details

Defined in Data.Default.Class

Methods

def :: CPtrdiff #

Default CSize 
Instance details

Defined in Data.Default.Class

Methods

def :: CSize #

Default CSigAtomic 
Instance details

Defined in Data.Default.Class

Methods

def :: CSigAtomic #

Default CClock 
Instance details

Defined in Data.Default.Class

Methods

def :: CClock #

Default CTime 
Instance details

Defined in Data.Default.Class

Methods

def :: CTime #

Default CUSeconds 
Instance details

Defined in Data.Default.Class

Methods

def :: CUSeconds #

Default CSUSeconds 
Instance details

Defined in Data.Default.Class

Methods

def :: CSUSeconds #

Default CIntPtr 
Instance details

Defined in Data.Default.Class

Methods

def :: CIntPtr #

Default CUIntPtr 
Instance details

Defined in Data.Default.Class

Methods

def :: CUIntPtr #

Default CIntMax 
Instance details

Defined in Data.Default.Class

Methods

def :: CIntMax #

Default CUIntMax 
Instance details

Defined in Data.Default.Class

Methods

def :: CUIntMax #

Default ExternalCompilerOpts 
Instance details

Defined in Language.Embedded.Backend.C

Default CompilerOpts Source # 
Instance details

Defined in Feldspar.Run.Compile

Methods

def :: CompilerOpts #

Default [a] 
Instance details

Defined in Data.Default.Class

Methods

def :: [a] #

Default (Maybe a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Maybe a #

Integral a => Default (Ratio a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Ratio a #

Default a => Default (IO a) 
Instance details

Defined in Data.Default.Class

Methods

def :: IO a #

(Default a, RealFloat a) => Default (Complex a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Complex a #

Default (First a) 
Instance details

Defined in Data.Default.Class

Methods

def :: First a #

Default (Last a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Last a #

Default a => Default (Dual a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Dual a #

Default (Endo a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Endo a #

Num a => Default (Sum a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Sum a #

Num a => Default (Product a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Product a #

Default r => Default (e -> r) 
Instance details

Defined in Data.Default.Class

Methods

def :: e -> r #

(Default a, Default b) => Default (a, b) 
Instance details

Defined in Data.Default.Class

Methods

def :: (a, b) #

(Default a, Default b, Default c) => Default (a, b, c) 
Instance details

Defined in Data.Default.Class

Methods

def :: (a, b, c) #

(Default a, Default b, Default c, Default d) => Default (a, b, c, d) 
Instance details

Defined in Data.Default.Class

Methods

def :: (a, b, c, d) #

(Default a, Default b, Default c, Default d, Default e) => Default (a, b, c, d, e) 
Instance details

Defined in Data.Default.Class

Methods

def :: (a, b, c, d, e) #

(Default a, Default b, Default c, Default d, Default e, Default f) => Default (a, b, c, d, e, f) 
Instance details

Defined in Data.Default.Class

Methods

def :: (a, b, c, d, e, f) #

(Default a, Default b, Default c, Default d, Default e, Default f, Default g) => Default (a, b, c, d, e, f, g) 
Instance details

Defined in Data.Default.Class

Methods

def :: (a, b, c, d, e, f, g) #

Back ends

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

Interpret a program in the IO monad

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.