ivory-0.1.0.3: Safe embedded C programming.

Safe HaskellNone
LanguageHaskell2010

Ivory.Language.Proc

Synopsis

Documentation

data Proc k Source

The kind of procedures.

Constructors

[k] :-> k 

class ProcType sig where Source

Typeclass for procedure types, parametrized over the C procedure's signature, to produce a value representing their signature.

Methods

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

Turn a type-level description of the signature into a (return type, [argument types]) value.

Instances

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

newtype ProcPtr sig Source

Procedure pointers

Constructors

ProcPtr 

Fields

getProcPtr :: Name
 

Instances

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

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

data Def proc Source

Procedure definitions.

Constructors

DefProc Proc 
DefImport Import 

Instances

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

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

Procedure definition.

voidProc :: IvoryProcDef (args :-> ()) impl => Sym -> impl -> Def (args :-> ()) Source

Type inference can usually determine the argument types of an Ivory procedure, but for void procedures there's often nothing to constrain the return type. This function is a type-constrained version of proc that just forces the return type to be '()'.

newtype Body r Source

Constructors

Body 

Fields

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

Instances

WrapIvory Body Source 
IvoryType ret => IvoryProcDef ((:->) * ([] *) ret) (Body ret) Source 
type Return Body = () Source 

class WrapIvory m where Source

Associated Types

type Return m Source

Methods

wrap :: (forall s. Ivory (ProcEffects s r) (Return m)) -> m r Source

unwrap :: m r -> forall s. Ivory (ProcEffects s r) (Return m) Source

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

class ProcType proc => IvoryProcDef proc impl | impl -> proc where Source

Typeclass for an Ivory procedure definition to produce ; the type is parametrized over:

  • The procedure type proc, encoding the C procedure's signature via the Proc kind,
  • The implementation type impl - either Body for the return value, or else a Haskell function type whose arguments correspond to the C arguments and whose return type is Body r on the return type r.

Methods

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

Instances

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

data Closure Source

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

Constructors

Closure 

Fields

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

initialClosure :: Closure Source

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.

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

Import a function from a C header.

newtype ImportFrom r Source

Constructors

ImportFrom 

Fields

runImportFrom :: forall s. Ivory (ProcEffects s r) FilePath
 

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

Direct calls.

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

Indirect calls.

class IvoryCall proc eff impl | proc eff -> impl, impl -> eff where Source

Typeclass for something callable in Ivory (and returning a result). Parameter proc is the procedure type (encoding the arguments and return of the C procedure via the Proc kind, as in IvoryProcDef), parameter eff is the effect context (which remains unchanged through the calls here), and parameter impl, as in IvoryProcDef, is the implementation type.

Methods

callAux :: Name -> Proxy proc -> [Typed Expr] -> impl Source

Recursive helper call. proc encodes a C procedure type, and this call has two main parts:

  • If proc contains arguments, then impl must be a function type causing this whole call to expect an Ivory value that was passed in to apply to the C procedure. In this case, proc is reduced by removing the first C argument from the type itself, and the argument to impl is accumulated onto the list of typed expressions.
  • If proc contains no arguments, then this returns the Ivory effect which calls the function with all the arguments in the list applied to it, and captures and returns the result.

Instances

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

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

Direct calls, ignoring the result.

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

Indirect calls, ignoring the result.

class IvoryCall_ proc eff impl | proc eff -> impl, impl -> eff where Source

Typeclass for something callable in Ivory without a return value needed. This is otherwise identical to IvoryCall.

Methods

callAux_ :: Name -> Proxy proc -> [Typed Expr] -> impl Source

Instances

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

ret :: (GetReturn eff ~ Returns r, IvoryVar r) => r -> Ivory eff () Source

Primitive return from function.

retVoid :: (GetReturn eff ~ Returns ()) => Ivory eff () Source

Primitive void return from function.