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

Safe HaskellNone
LanguageHaskell2010

Language.Embedded.Imperative.Frontend

Contents

Synopsis

References

newRef :: (VarPred (IExp instr) a, RefCMD (IExp instr) :<: instr) => ProgramT instr m (Ref a) Source

Create an uninitialized reference

initRef :: (VarPred (IExp instr) a, RefCMD (IExp instr) :<: instr) => IExp instr a -> ProgramT instr m (Ref a) Source

Create an initialized reference

getRef :: (VarPred (IExp instr) a, RefCMD (IExp instr) :<: instr) => Ref a -> ProgramT instr m (IExp instr a) Source

Get the contents of a reference

setRef :: (VarPred (IExp instr) a, RefCMD (IExp instr) :<: instr) => Ref a -> IExp instr a -> ProgramT instr m () Source

Set the contents of a reference

modifyRef :: (VarPred (IExp instr) a, EvalExp (IExp instr), CompExp (IExp instr), RefCMD (IExp instr) :<: instr, Monad m) => Ref a -> (IExp instr a -> IExp instr a) -> ProgramT instr m () Source

Modify the contents of reference

veryUnsafeFreezeRef :: (VarPred exp a, EvalExp exp, CompExp exp) => 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

unsafeFreezeRef :: (VarPred exp a, EvalExp exp, CompExp exp, Monad m) => Ref a -> ProgramT instr m (exp a) Source

Freeze the contents of reference (only safe if the reference is never written to after the freezing)

Arrays

newArr :: (pred a, pred i, Integral i, Ix i, ArrCMD (IExp instr) :<: instr, pred ~ VarPred (IExp instr)) => IExp instr i -> ProgramT instr m (Arr i a) Source

Create an uninitialized an array

newArr_ :: (pred a, pred i, Integral i, Ix i, ArrCMD (IExp instr) :<: instr, pred ~ VarPred (IExp instr)) => ProgramT instr m (Arr i a) Source

getArr :: (VarPred (IExp instr) a, ArrCMD (IExp instr) :<: instr, Integral i, Ix i) => IExp instr i -> Arr i a -> ProgramT instr m (IExp instr a) Source

Set the contents of an array

setArr :: (VarPred (IExp instr) a, ArrCMD (IExp instr) :<: instr, Integral i, Ix i) => IExp instr i -> IExp instr a -> Arr i a -> ProgramT instr m () Source

Set the contents of an array

Control flow

iff Source

Arguments

:: ControlCMD (IExp instr) :<: instr 
=> IExp instr Bool

Condition

-> ProgramT instr m ()

True branch

-> ProgramT instr m ()

False branch

-> ProgramT instr m () 

Conditional statement

ifE Source

Arguments

:: (VarPred (IExp instr) a, ControlCMD (IExp instr) :<: instr, RefCMD (IExp instr) :<: instr, Monad m) 
=> IExp instr Bool

Condition

-> ProgramT instr m (IExp instr a)

True branch

-> ProgramT instr m (IExp instr a)

False branch

-> ProgramT instr m (IExp instr a) 

Conditional statement that returns an expression

while Source

Arguments

:: ControlCMD (IExp instr) :<: instr 
=> ProgramT instr m (IExp instr Bool)

Continue condition

-> ProgramT instr m ()

Loop body

-> ProgramT instr m () 

While loop

whileE Source

Arguments

:: (VarPred (IExp instr) a, ControlCMD (IExp instr) :<: instr, RefCMD (IExp instr) :<: instr, Monad m) 
=> ProgramT instr m (IExp instr Bool)

Continue condition

-> ProgramT instr m (IExp instr a)

Loop body

-> ProgramT instr m (IExp instr a) 

While loop that returns an expression

for Source

Arguments

:: (ControlCMD (IExp instr) :<: instr, Integral n, VarPred (IExp instr) n) 
=> IExp instr n

Start index

-> IExp instr n

Stop index

-> (IExp instr n -> ProgramT instr m ())

Loop body

-> ProgramT instr m () 

For loop

forE Source

Arguments

:: (Integral n, VarPred (IExp instr) n, VarPred (IExp instr) a, ControlCMD (IExp instr) :<: instr, RefCMD (IExp instr) :<: instr, Monad m) 
=> IExp instr n

Start index

-> IExp instr n

Stop index

-> (IExp instr n -> ProgramT instr m (IExp instr a))

Loop body

-> ProgramT instr m (IExp instr a) 

For loop

break :: ControlCMD (IExp instr) :<: instr => ProgramT instr m () Source

Break out from a loop

File handling

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

Open a file

fclose :: FileCMD (IExp instr) :<: instr => Handle -> ProgramT instr m () Source

Close a file

feof :: (VarPred (IExp instr) Bool, FileCMD (IExp instr) :<: instr) => Handle -> ProgramT instr m (IExp instr 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, VarPred exp a, PrintfType r, (~) (* -> *) exp (PrintfExp r)) => PrintfType (exp a -> r) Source 
((:<:) (* -> *) * (FileCMD (IExp instr)) instr, (~) * a ()) => PrintfType (ProgramT instr 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 (IExp instr) a, FileCMD (IExp instr) :<: instr) 
=> Handle 
-> String

Prefix

-> IExp instr a

Expression to print

-> String

Suffix

-> ProgramT instr m () 

Put a single value to a handle

fget :: (Formattable a, VarPred (IExp instr) a, FileCMD (IExp instr) :<: instr) => Handle -> ProgramT instr m (IExp instr a) Source

Get a single value from a handle

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

Print to stdout. Accepts a variable number of arguments.

Abstract objects

newObject Source

Arguments

:: ObjectCMD (IExp instr) :<: instr 
=> String

Object type

-> ProgramT instr 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.

initObject Source

Arguments

:: ObjectCMD (IExp instr) :<: instr 
=> String

Function name

-> String

Object type

-> [FunArg (IExp instr)]

Arguments

-> ProgramT instr m Object 

Call a function to create a pointed object

initUObject Source

Arguments

:: ObjectCMD (IExp instr) :<: instr 
=> String

Function name

-> String

Object type

-> [FunArg (IExp instr)]

Arguments

-> ProgramT instr m Object 

Call a function to create an object

External function calls (C-specific)

addInclude :: CallCMD (IExp instr) :<: instr => String -> ProgramT instr m () Source

Add an #include statement to the generated code

addDefinition :: CallCMD (IExp instr) :<: instr => Definition -> ProgramT instr 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

:: (VarPred exp res, CallCMD exp :<: instr, exp ~ IExp instr) 
=> String

Function name

-> proxy (exp res)

Proxy for expression and result type

-> [FunArg exp]

Arguments (only used to determine types)

-> ProgramT instr m () 

Declare an external function

addExternProc Source

Arguments

:: (CallCMD exp :<: instr, exp ~ IExp instr) 
=> String

Procedure name

-> [FunArg exp]

Arguments (only used to determine types)

-> ProgramT instr m () 

Declare an external procedure

callFun Source

Arguments

:: (VarPred (IExp instr) a, CallCMD (IExp instr) :<: instr) 
=> String

Function name

-> [FunArg (IExp instr)]

Arguments

-> ProgramT instr m (IExp instr a) 

Call a function

callProc Source

Arguments

:: CallCMD (IExp instr) :<: instr 
=> String

Procedure name

-> [FunArg (IExp instr)]

Arguments

-> ProgramT instr m () 

Call a procedure

externFun Source

Arguments

:: (VarPred exp res, CallCMD exp :<: instr, exp ~ IExp instr, Monad m) 
=> String

Function name

-> [FunArg exp]

Arguments

-> ProgramT instr m (exp res) 

Declare and call an external function

externProc Source

Arguments

:: (CallCMD exp :<: instr, exp ~ IExp instr, Monad m) 
=> String

Procedure name

-> [FunArg exp]

Arguments

-> ProgramT instr m () 

Declare and call an external procedure

getTime :: (VarPred (IExp instr) Double, CallCMD (IExp instr) :<: instr, Monad m) => ProgramT instr m (IExp instr Double) Source

Get current time as number of seconds passed today

strArg :: String -> FunArg exp Source

Constant string argument

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

Value argument

refArg :: VarPred exp a => Ref a -> FunArg exp Source

Reference argument

arrArg :: VarPred exp a => Arr n a -> FunArg exp Source

Array argument

objArg :: Object -> FunArg exp Source

Abstract object argument

addr :: FunArg exp -> FunArg exp Source

Modifier that takes the address of another argument

Running programs

runIO :: (Interp instr IO, HFunctor instr) => Program instr 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.