ivory-0.1.0.0: Safe embedded C programming.

Safe HaskellNone

Ivory.Language.Proc

Synopsis

Documentation

data Proc k Source

The kind of procedures.

Constructors

[k] :-> k 

class ProcType sig whereSource

Methods

procType :: Proxy sig -> (Type, [Type])Source

Instances

(IvoryType a, ProcType (:-> * args r)) => ProcType (:-> * (: * a args) r) 
IvoryType r => ProcType (:-> * ([] *) r) 

newtype ProcPtr sig Source

Procedure pointers

Constructors

ProcPtr 

Fields

getProcPtr :: Name
 

Instances

ProcType proc => IvoryVar (ProcPtr proc) 
ProcType proc => IvoryType (ProcPtr proc) 
ProcType proc => IvoryInit (ProcPtr proc) 

procPtr :: ProcType sig => Def sig -> ProcPtr sigSource

data Def proc Source

Procedure definitions.

Instances

Eq (Def proc) 
Ord (Def proc) 
Show (Def proc) 
ProcType proc => IvoryType (Def proc) 

proc :: forall proc impl. IvoryProcDef proc impl => Sym -> impl -> Def procSource

Procedure definition.

newtype Body r Source

Constructors

Body 

Fields

runBody :: forall s. Ivory (ProcEffects s r) ()
 

Instances

IvoryType ret => IvoryProcDef (:-> * ([] *) ret) (Body ret) 

body :: IvoryType r => (forall s. Ivory (ProcEffects s r) ()) -> Body rSource

class ProcType proc => IvoryProcDef proc impl | impl -> proc whereSource

Methods

procDef :: Closure -> Proxy proc -> impl -> ([Var], CodeBlock)Source

Instances

IvoryType ret => IvoryProcDef (:-> * ([] *) ret) (Body ret) 
(IvoryVar a, IvoryProcDef (:-> * args ret) k) => IvoryProcDef (:-> * (: * a args) ret) (a -> k) 

data Closure Source

A variable name supply, and the typed values that have been generated.

Constructors

Closure 

Fields

closSupply :: [Var]
 
closEnv :: [Var]
 

initialClosure :: ClosureSource

Initial closure, with no environment and a large supply of names.

genVar :: Closure -> (Var, Closure)Source

Given a type and a closure, generate a typed variable, and a new closure with that typed variable in it's environment.

getEnv :: Closure -> [Var]Source

Retrieve the environment from a closure.

externProc :: forall proc. ProcType proc => Sym -> Def procSource

External function reference.

importProc :: forall proc. ProcType proc => Sym -> String -> Def procSource

Import a function from a C header.

call :: forall proc eff impl. IvoryCall proc eff impl => Def proc -> implSource

Direct calls.

indirect :: forall proc eff impl. IvoryCall proc eff impl => ProcPtr proc -> implSource

Indirect calls.

class IvoryCall proc eff impl | proc eff -> impl, impl -> eff whereSource

Methods

callAux :: Name -> Proxy proc -> [Typed Expr] -> implSource

Instances

(IvoryVar a, IvoryVar r, IvoryCall (:-> * args r) eff impl) => IvoryCall (:-> * (: * a args) r) eff (a -> impl) 
IvoryVar r => IvoryCall (:-> * ([] *) r) eff (Ivory eff r) 

call_ :: forall proc eff impl. IvoryCall_ proc eff impl => Def proc -> implSource

Direct calls, ignoring the result.

indirect_ :: forall proc eff impl. IvoryCall_ proc eff impl => ProcPtr proc -> implSource

Indirect calls, ignoring the result.

class IvoryCall_ proc eff impl | proc eff -> impl, impl -> eff whereSource

Methods

callAux_ :: Name -> Proxy proc -> [Typed Expr] -> implSource

Instances

(IvoryVar a, IvoryType r, IvoryCall_ (:-> * args r) eff impl) => IvoryCall_ (:-> * (: * a args) r) eff (a -> impl) 
IvoryType r => IvoryCall_ (:-> * ([] *) r) eff (Ivory eff ())