| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Feldspar.Run.Frontend
Description
Monad for running Feldspar programs
- data Run a
- class Monad m => MonadRun m where
- unsafeSwap :: IsPointer a => a -> a -> Run ()
- unsafeSwapArr :: Arr a -> Arr a -> Run ()
- fopen :: FilePath -> IOMode -> Run Handle
- fclose :: Handle -> Run ()
- feof :: Handle -> Run (Data Bool)
- class PrintfType r where
- fprintf :: PrintfType r => Handle -> String -> r
- fput :: (Formattable a, PrimType a) => Handle -> String -> Data a -> String -> Run ()
- fget :: (Formattable a, PrimType a) => Handle -> Run (Data a)
- printf :: PrintfType r => String -> r
- newPtr :: PrimType a => Run (Ptr a)
- newNamedPtr :: PrimType a => String -> Run (Ptr a)
- ptrToArr :: PrimType a => Ptr a -> Data Length -> Run (DArr a)
- newObject :: String -> Bool -> Run Object
- newNamedObject :: String -> String -> Bool -> Run Object
- addInclude :: String -> Run ()
- addDefinition :: Definition -> Run ()
- addExternFun :: PrimType res => String -> proxy res -> [FunArg Data PrimType'] -> Run ()
- addExternProc :: String -> [FunArg Data PrimType'] -> Run ()
- callFun :: PrimType a => String -> [FunArg Data PrimType'] -> Run (Data a)
- callProc :: String -> [FunArg Data PrimType'] -> Run ()
- callProcAssign :: Assignable obj => obj -> String -> [FunArg Data PrimType'] -> Run ()
- externFun :: PrimType res => String -> [FunArg Data PrimType'] -> Run (Data res)
- externProc :: String -> [FunArg Data PrimType'] -> Run ()
- inModule :: String -> Run () -> Run ()
- getTime :: Run (Data Double)
- strArg :: String -> FunArg Data PrimType'
- valArg :: PrimType' a => Data a -> FunArg Data PrimType'
- refArg :: PrimType' (Internal a) => Ref a -> FunArg Data PrimType'
- arrArg :: PrimType' (Internal a) => Arr a -> FunArg Data PrimType'
- iarrArg :: PrimType' (Internal a) => IArr a -> FunArg Data PrimType'
- objArg :: Object -> FunArg Data PrimType'
- constArg :: String -> String -> FunArg Data PrimType'
- addr :: FunArg Data PrimType' -> FunArg Data PrimType'
- deref :: FunArg Data PrimType' -> FunArg Data PrimType'
- module Language.Embedded.Imperative.Frontend.General
Documentation
Monad for running Feldspar programs
Pointer operations
unsafeSwap :: IsPointer a => a -> a -> Run () Source #
Swap two pointers
This is generally an unsafe operation. E.g. it can be used to make a reference to a data structure escape the scope of the data.
The IsPointer class ensures that the operation is only possible for types
that are represented as pointers in C.
unsafeSwapArr :: Arr a -> Arr a -> Run () Source #
Like unsafeSwap but for arrays. The why we cannot use unsafeSwap
directly is that Arr cannot be made an instance of IsPointer.
File handling
class PrintfType r where Source #
Minimal complete definition
Instances
| (~) * a () => PrintfType (Run a) Source # | |
| (Formattable a, PrimType a, PrintfType r) => PrintfType (Data a -> r) Source # | |
fprintf :: PrintfType r => Handle -> String -> r Source #
Print to a handle. Accepts a variable number of arguments.
fput :: (Formattable a, PrimType a) => Handle -> String -> Data a -> String -> Run () Source #
Put a primitive value to a handle
fget :: (Formattable a, PrimType a) => Handle -> Run (Data a) Source #
Get a primitive value from a handle
printf :: PrintfType r => String -> r Source #
Print to stdout. Accepts a variable number of arguments.
C-specific commands
Create a named null pointer
The provided base name may be appended with a unique identifier to avoid name collisions.
addInclude :: String -> Run () Source #
Add an #include statement to the generated code
addDefinition :: Definition -> Run () Source #
Add a global definition to the generated code
Can be used conveniently as follows:
{-# LANGUAGE QuasiQuotes #-}
import Feldspar.IO
prog = do
...
addDefinition myCFunction
...
where
myCFunction = [cedecl|
void my_C_function( ... )
{
// C code
// goes here
}
|]Arguments
| :: PrimType res | |
| => String | Function name |
| -> proxy res | Proxy for expression and result type |
| -> [FunArg Data PrimType'] | Arguments (only used to determine types) |
| -> Run () |
Declare an external function
Arguments
| :: String | Procedure name |
| -> [FunArg Data PrimType'] | Arguments (only used to determine types) |
| -> Run () |
Declare an external procedure
Call a function
Call a procedure
Arguments
| :: Assignable obj | |
| => obj | Object to which the result should be assigned |
| -> String | Procedure name |
| -> [FunArg Data PrimType'] | Arguments |
| -> Run () |
Call a procedure and assign its result
Arguments
| :: PrimType res | |
| => String | Procedure name |
| -> [FunArg Data PrimType'] | Arguments |
| -> Run (Data res) |
Declare and call an external function
Declare and call an external procedure
iarrArg :: PrimType' (Internal a) => IArr a -> FunArg Data PrimType' Source #
Immutable array argument
Named constant argument
addr :: FunArg Data PrimType' -> FunArg Data PrimType' Source #
Modifier that takes the address of another argument