raw-feldspar-0.1: Resource-Aware Feldspar

Safe HaskellNone
LanguageHaskell2010

Feldspar.Run.Frontend

Contents

Description

Monad for running Feldspar programs

Synopsis

Documentation

data Run a Source #

Monad for running Feldspar programs

Instances

Monad Run Source # 

Methods

(>>=) :: Run a -> (a -> Run b) -> Run b #

(>>) :: Run a -> Run b -> Run b #

return :: a -> Run a #

fail :: String -> Run a #

Functor Run Source # 

Methods

fmap :: (a -> b) -> Run a -> Run b #

(<$) :: a -> Run b -> Run a #

Applicative Run Source # 

Methods

pure :: a -> Run a #

(<*>) :: Run (a -> b) -> Run a -> Run b #

(*>) :: Run a -> Run b -> Run b #

(<*) :: Run a -> Run b -> Run a #

MonadComp Run Source # 

Methods

liftComp :: Comp a -> Run a Source #

iff :: Data Bool -> Run () -> Run () -> Run () Source #

for :: (Integral n, PrimType n) => IxRange (Data n) -> (Data n -> Run ()) -> Run () Source #

while :: Run (Data Bool) -> Run () -> Run () Source #

MonadRun Run Source # 

Methods

liftRun :: Run a -> Run a Source #

(~) * a () => PrintfType (Run a) Source # 

Methods

fprf :: Handle -> String -> [PrintfArg Data] -> Run a Source #

class Monad m => MonadRun m where Source #

Minimal complete definition

liftRun

Methods

liftRun :: m a -> Run a Source #

Instances

MonadRun Comp Source # 

Methods

liftRun :: Comp a -> Run a Source #

MonadRun Run Source # 

Methods

liftRun :: Run a -> Run a Source #

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

fopen :: FilePath -> IOMode -> Run Handle Source #

Open a file

fclose :: Handle -> Run () Source #

Close a file

feof :: Handle -> Run (Data Bool) Source #

Check for end of file

class PrintfType r where Source #

Minimal complete definition

fprf

Methods

fprf :: Handle -> String -> [PrintfArg Data] -> r Source #

Instances

(~) * a () => PrintfType (Run a) Source # 

Methods

fprf :: Handle -> String -> [PrintfArg Data] -> Run a Source #

(Formattable a, PrimType a, PrintfType r) => PrintfType (Data a -> r) Source # 

Methods

fprf :: Handle -> String -> [PrintfArg Data] -> 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

newPtr :: PrimType a => Run (Ptr a) Source #

Create a null pointer

newNamedPtr Source #

Arguments

:: PrimType a 
=> String

Base name

-> Run (Ptr a) 

Create a named null pointer

The provided base name may be appended with a unique identifier to avoid name collisions.

ptrToArr :: PrimType a => Ptr a -> Data Length -> Run (DArr a) Source #

Cast a pointer to an array

newObject Source #

Arguments

:: String

Object type

-> Bool

Pointed?

-> Run Object 

Create a pointer to an abstract object. The only thing one can do with such objects is to pass them to callFun or callProc.

newNamedObject Source #

Arguments

:: String

Base name

-> String

Object type

-> Bool

Pointed?

-> Run Object 

Create a pointer to an abstract object. The only thing one can do with such objects is to pass them to callFun or callProc.

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
      }
      |]

addExternFun Source #

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

addExternProc Source #

Arguments

:: String

Procedure name

-> [FunArg Data PrimType']

Arguments (only used to determine types)

-> Run () 

Declare an external procedure

callFun Source #

Arguments

:: PrimType a 
=> String

Function name

-> [FunArg Data PrimType']

Arguments

-> Run (Data a) 

Call a function

callProc Source #

Arguments

:: String

Function name

-> [FunArg Data PrimType']

Arguments

-> Run () 

Call a procedure

callProcAssign Source #

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

externFun Source #

Arguments

:: PrimType res 
=> String

Procedure name

-> [FunArg Data PrimType']

Arguments

-> Run (Data res) 

Declare and call an external function

externProc Source #

Arguments

:: String

Procedure name

-> [FunArg Data PrimType']

Arguments

-> Run () 

Declare and call an external procedure

inModule :: String -> Run () -> Run () Source #

Generate code into another translation unit

getTime :: Run (Data Double) Source #

Get current time as number of seconds passed today

strArg :: String -> FunArg Data PrimType' Source #

Constant string argument

valArg :: PrimType' a => Data a -> FunArg Data PrimType' Source #

Value argument

refArg :: PrimType' (Internal a) => Ref a -> FunArg Data PrimType' Source #

Reference argument

arrArg :: PrimType' (Internal a) => Arr a -> FunArg Data PrimType' Source #

Mutable array argument

iarrArg :: PrimType' (Internal a) => IArr a -> FunArg Data PrimType' Source #

Immutable array argument

objArg :: Object -> FunArg Data PrimType' Source #

Abstract object argument

constArg Source #

Arguments

:: String

Type

-> String

Named constant

-> FunArg Data PrimType' 

Named constant argument

addr :: FunArg Data PrimType' -> FunArg Data PrimType' Source #

Modifier that takes the address of another argument

deref :: FunArg Data PrimType' -> FunArg Data PrimType' Source #

Modifier that dereferences another argument