imperative-edsl-0.5: Deep embedding of imperative programs with code generation

Safe HaskellNone
LanguageHaskell2010

Language.Embedded.Imperative.Frontend

Contents

Synopsis

References

newRef :: (pred a, RefCMD :<: instr) => ProgramT instr (Param2 exp pred) m (Ref a) Source

Create an uninitialized reference

newNamedRef Source

Arguments

:: (pred a, RefCMD :<: instr) 
=> String

Base name

-> ProgramT instr (Param2 exp pred) m (Ref a) 

Create an uninitialized named reference

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

initRef Source

Arguments

:: (pred a, RefCMD :<: instr) 
=> exp a

Initial value

-> ProgramT instr (Param2 exp pred) m (Ref a) 

Create an initialized reference

initNamedRef Source

Arguments

:: (pred a, RefCMD :<: instr) 
=> String

Base name

-> exp a

Initial value

-> ProgramT instr (Param2 exp pred) m (Ref a) 

Create an initialized named reference

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

getRef :: (pred a, FreeExp exp, VarPred exp a, RefCMD :<: instr, Monad m) => Ref a -> ProgramT instr (Param2 exp pred) m (exp a) Source

Get the contents of a reference

setRef :: (pred a, RefCMD :<: instr) => Ref a -> exp a -> ProgramT instr (Param2 exp pred) m () Source

Set the contents of a reference

modifyRef :: (pred a, FreeExp exp, VarPred exp a, RefCMD :<: instr, Monad m) => Ref a -> (exp a -> exp a) -> ProgramT instr (Param2 exp pred) m () Source

Modify the contents of reference

unsafeFreezeRef :: (pred a, FreeExp exp, VarPred exp a, RefCMD :<: instr, Monad m) => Ref a -> ProgramT instr (Param2 exp pred) m (exp a) Source

Freeze the contents of reference (only safe if the reference is not updated as long as the resulting value is alive)

veryUnsafeFreezeRef :: (FreeExp exp, VarPred exp a) => Ref a -> exp a Source

Read the value of a reference without returning in the monad

WARNING: Don't use this function unless you really know what you are doing. It is almost always better to use unsafeFreezeRef instead.

veryUnsafeFreezeRef behaves predictably when doing code generation, but it can give strange results when evaluating in IO, as explained here:

http://fun-discoveries.blogspot.se/2015/09/strictness-can-fix-non-termination.html

Arrays

newArr Source

Arguments

:: (pred a, Integral i, Ix i, ArrCMD :<: instr) 
=> exp i

Length

-> ProgramT instr (Param2 exp pred) m (Arr i a) 

Create an uninitialized array

newNamedArr Source

Arguments

:: (pred a, Integral i, Ix i, ArrCMD :<: instr) 
=> String

Base name

-> exp i

Length

-> ProgramT instr (Param2 exp pred) m (Arr i a) 

Create an uninitialized named array

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

initArr Source

Arguments

:: (pred a, Integral i, Ix i, ArrCMD :<: instr) 
=> [a]

Initial contents

-> ProgramT instr (Param2 exp pred) m (Arr i a) 

Create and initialize an array

initNamedArr Source

Arguments

:: (pred a, Integral i, Ix i, ArrCMD :<: instr) 
=> String

Base name

-> [a]

Initial contents

-> ProgramT instr (Param2 exp pred) m (Arr i a) 

Create and initialize a named array

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

getArr :: (pred a, FreeExp exp, VarPred exp a, Integral i, Ix i, ArrCMD :<: instr, Monad m) => exp i -> Arr i a -> ProgramT instr (Param2 exp pred) m (exp a) Source

Get an element of an array

setArr :: (pred a, Integral i, Ix i, ArrCMD :<: instr) => exp i -> exp a -> Arr i a -> ProgramT instr (Param2 exp pred) m () Source

Set an element of an array

copyArr Source

Arguments

:: (pred a, Integral i, Ix i, ArrCMD :<: instr) 
=> Arr i a

Destination

-> Arr i a

Source

-> exp i

Number of elements

-> ProgramT instr (Param2 exp pred) m () 

Copy the contents of an array to another array. The number of elements to copy must not be greater than the number of allocated elements in either array.

freezeArr Source

Arguments

:: (pred a, Integral i, Ix i, ArrCMD :<: instr, Monad m) 
=> Arr i a 
-> exp i

Length of new array

-> ProgramT instr (Param2 exp pred) m (IArr i a) 

Freeze a mutable array to an immutable one. This involves copying the array to a newly allocated one.

unsafeFreezeArr :: (pred a, Integral i, Ix i, ArrCMD :<: instr) => Arr i a -> ProgramT instr (Param2 exp pred) m (IArr i a) Source

Freeze a mutable array to an immutable one without making a copy. This is generally only safe if the the mutable array is not updated as long as the immutable array is alive.

thawArr Source

Arguments

:: (pred a, Integral i, Ix i, ArrCMD :<: instr, Monad m) 
=> IArr i a 
-> exp i

Number of elements to copy

-> ProgramT instr (Param2 exp pred) m (Arr i a) 

Thaw an immutable array to a mutable one. This involves copying the array to a newly allocated one.

unsafeThawArr :: (pred a, Integral i, Ix i, ArrCMD :<: instr) => IArr i a -> ProgramT instr (Param2 exp pred) m (Arr i a) Source

Thaw an immutable array to a mutable one without making a copy. This is generally only safe if the the mutable array is not updated as long as the immutable array is alive.

initIArr :: (pred a, Integral i, Ix i, ArrCMD :<: instr, Monad m) => [a] -> ProgramT instr (Param2 exp pred) m (IArr i a) Source

Create and initialize an immutable array

Control flow

iff Source

Arguments

:: ControlCMD :<: instr 
=> exp Bool

Condition

-> ProgramT instr (Param2 exp pred) m ()

True branch

-> ProgramT instr (Param2 exp pred) m ()

False branch

-> ProgramT instr (Param2 exp pred) m () 

Conditional statement

ifE Source

Arguments

:: (pred a, FreeExp exp, VarPred exp a, ControlCMD :<: instr, RefCMD :<: instr, Monad m) 
=> exp Bool

Condition

-> ProgramT instr (Param2 exp pred) m (exp a)

True branch

-> ProgramT instr (Param2 exp pred) m (exp a)

False branch

-> ProgramT instr (Param2 exp pred) m (exp a) 

Conditional statement that returns an expression

while Source

Arguments

:: ControlCMD :<: instr 
=> ProgramT instr (Param2 exp pred) m (exp Bool)

Continue condition

-> ProgramT instr (Param2 exp pred) m ()

Loop body

-> ProgramT instr (Param2 exp pred) m () 

While loop

for Source

Arguments

:: (FreeExp exp, ControlCMD :<: instr, Integral n, pred n, VarPred exp n) 
=> IxRange (exp n)

Index range

-> (exp n -> ProgramT instr (Param2 exp pred) m ())

Loop body

-> ProgramT instr (Param2 exp pred) m () 

For loop

break :: ControlCMD :<: instr => ProgramT instr (Param2 exp pred) m () Source

Break out from a loop

assert Source

Arguments

:: ControlCMD :<: instr 
=> exp Bool

Expression that should be true

-> String

Message in case of failure

-> ProgramT instr (Param2 exp pred) m () 

Assertion

Pointer operations

unsafeSwap :: (IsPointer a, PtrCMD :<: instr) => a -> a -> ProgramT instr (Param2 exp pred) m () 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.

File handling

fopen :: FileCMD :<: instr => FilePath -> IOMode -> ProgramT instr (Param2 exp pred) m Handle Source

Open a file

fclose :: FileCMD :<: instr => Handle -> ProgramT instr (Param2 exp pred) m () Source

Close a file

feof :: (FreeExp exp, VarPred exp Bool, FileCMD :<: instr, Monad m) => Handle -> ProgramT instr (Param2 exp pred) m (exp Bool) Source

Check for end of file

class PrintfType r where Source

Associated Types

type PrintfExp r :: * -> * Source

Methods

fprf :: Handle -> String -> [PrintfArg (PrintfExp r)] -> r Source

Instances

(Formattable a, PrintfType r, (~) (* -> *) exp (PrintfExp r)) => PrintfType (exp a -> r) Source 
((:<:) ((,) (* -> *) ((,) (* -> *) ((,) (* -> Constraint) *))) * (FileCMD (* -> *)) instr, (~) * a ()) => PrintfType (ProgramT ((,) (* -> *) ((,) (* -> Constraint) *)) instr (Param2 (* -> *) (* -> Constraint) exp pred) m a) Source 

fprintf :: PrintfType r => Handle -> String -> r Source

Print to a handle. Accepts a variable number of arguments.

fput Source

Arguments

:: (Formattable a, VarPred exp a, FileCMD :<: instr) 
=> Handle 
-> String

Prefix

-> exp a

Expression to print

-> String

Suffix

-> ProgramT instr (Param2 exp pred) m () 

Put a single value to a handle

fget :: (Formattable a, pred a, FreeExp exp, VarPred exp a, FileCMD :<: instr, Monad m) => Handle -> ProgramT instr (Param2 exp pred) m (exp a) Source

Get a single value from a handle

printf :: PrintfType r => String -> r Source

Print to stdout. Accepts a variable number of arguments.

C-specific commands

newPtr :: (pred a, C_CMD :<: instr) => ProgramT instr (Param2 exp pred) m (Ptr a) Source

Create a null pointer

newNamedPtr Source

Arguments

:: (pred a, C_CMD :<: instr) 
=> String

Base name

-> ProgramT instr (Param2 exp pred) m (Ptr a) 

Create a named null pointer

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

ptrToArr :: C_CMD :<: instr => Ptr a -> ProgramT instr (Param2 exp pred) m (Arr i a) Source

Cast a pointer to an array

newObject Source

Arguments

:: C_CMD :<: instr 
=> String

Object type

-> Bool

Pointed?

-> ProgramT instr (Param2 exp pred) m 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

:: C_CMD :<: instr 
=> String

Base name

-> String

Object type

-> Bool

Pointed?

-> ProgramT instr (Param2 exp pred) m Object 

Create a pointer to a named 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.

inModule :: C_CMD :<: instr => String -> ProgramT instr (Param2 exp pred) m () -> ProgramT instr (Param2 exp pred) m () Source

Generate code into another translation unit

addInclude :: C_CMD :<: instr => String -> ProgramT instr (Param2 exp pred) m () Source

Add an #include statement to the generated code

addDefinition :: C_CMD :<: instr => Definition -> ProgramT instr (Param2 exp pred) m () Source

Add a global definition to the generated code

Can be used conveniently as follows:

{-# LANGUAGE QuasiQuotes #-}

import Language.Embedded.Imperative
import Language.C.Quote.C

prog = do
    ...
    addDefinition myCFunction
    ...
  where
    myCFunction = [cedecl|
      void my_C_function( ... )
      {
          // C code
          // goes here
      }
      |]

addExternFun Source

Arguments

:: (pred res, C_CMD :<: instr) 
=> String

Function name

-> proxy res

Proxy for result type

-> [FunArg exp pred]

Arguments (only used to determine types)

-> ProgramT instr (Param2 exp pred) m () 

Declare an external function

addExternProc Source

Arguments

:: C_CMD :<: instr 
=> String

Procedure name

-> [FunArg exp pred]

Arguments (only used to determine types)

-> ProgramT instr (Param2 exp pred) m () 

Declare an external procedure

callFun Source

Arguments

:: (pred a, FreeExp exp, VarPred exp a, C_CMD :<: instr, Monad m) 
=> String

Function name

-> [FunArg exp pred]

Arguments

-> ProgramT instr (Param2 exp pred) m (exp a) 

Call a function

callProc Source

Arguments

:: C_CMD :<: instr 
=> String

Procedure name

-> [FunArg exp pred]

Arguments

-> ProgramT instr (Param2 exp pred) m () 

Call a procedure

callProcAssign Source

Arguments

:: (Assignable obj, C_CMD :<: instr) 
=> obj

Object to which the result should be assigned

-> String

Procedure name

-> [FunArg exp pred]

Arguments

-> ProgramT instr (Param2 exp pred) m () 

Call a procedure and assign its result

externFun Source

Arguments

:: (pred res, FreeExp exp, VarPred exp res, C_CMD :<: instr, Monad m) 
=> String

Function name

-> [FunArg exp pred]

Arguments

-> ProgramT instr (Param2 exp pred) m (exp res) 

Declare and call an external function

externProc Source

Arguments

:: (C_CMD :<: instr, Monad m) 
=> String

Procedure name

-> [FunArg exp pred]

Arguments

-> ProgramT instr (Param2 exp pred) m () 

Declare and call an external procedure

getTime :: (pred Double, FreeExp exp, VarPred exp Double, C_CMD :<: instr, Monad m) => ProgramT instr (Param2 exp pred) m (exp Double) Source

Get current time as number of seconds passed today

valArg :: pred a => exp a -> FunArg exp pred Source

Value argument

refArg :: (pred a, Arg RefArg pred) => Ref a -> FunArg exp pred Source

Reference argument

arrArg :: (pred a, Arg ArrArg pred) => Arr i a -> FunArg exp pred Source

Mutable array argument

iarrArg :: (pred a, Arg IArrArg pred) => IArr i a -> FunArg exp pred Source

Immutable array argument

ptrArg :: (pred a, Arg PtrArg pred) => Ptr a -> FunArg exp pred Source

Pointer argument

objArg :: Object -> FunArg exp pred Source

Abstract object argument

strArg :: String -> FunArg exp pred Source

Constant string argument

addr :: FunArg exp pred -> FunArg exp pred Source

Modifier that takes the address of another argument

deref :: FunArg exp pred -> FunArg exp pred Source

Modifier that dereferences another argument

Running programs

runIO :: (EvalExp exp, InterpBi instr IO (Param1 pred), HBifunctor instr) => Program instr (Param2 exp pred) a -> IO a Source

Run a program in IO. Note that not all instructions are supported for running in IO. For example, calls to external C functions are not supported.

captureIO Source

Arguments

:: (EvalExp exp, InterpBi instr IO (Param1 pred), HBifunctor instr) 
=> Program instr (Param2 exp pred) a

Program to run

-> String

Input to send to stdin

-> IO String

Result from stdout

Like runIO but with explicit inputoutput connected to stdinstdout