Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Proc k = [k] :-> k
- class ProcType sig where
- newtype ProcPtr sig = ProcPtr {
- getProcPtr :: Name
- procPtr :: ProcType sig => Def sig -> ProcPtr sig
- data Def proc
- defSymbol :: Def proc -> Name
- proc :: forall proc impl. IvoryProcDef proc impl => Sym -> impl -> Def proc
- voidProc :: IvoryProcDef (args :-> ()) impl => Sym -> impl -> Def (args :-> ())
- newtype Body r = Body {
- runBody :: forall s. Ivory (ProcEffects s r) ()
- class WrapIvory m where
- type Return m
- body :: IvoryType r => (forall s. Ivory (ProcEffects s r) ()) -> Body r
- data Definition
- class ProcType proc => IvoryProcDef proc impl | impl -> proc where
- data Closure = Closure {
- closSupply :: [Var]
- closEnv :: [Var]
- initialClosure :: Closure
- genVar :: Closure -> (Var, Closure)
- getEnv :: Closure -> [Var]
- importProc :: forall proc. ProcType proc => Sym -> String -> Def proc
- newtype ImportFrom r = ImportFrom {
- runImportFrom :: forall s. Ivory (ProcEffects s r) FilePath
- importFrom :: String -> ImportFrom a
- call :: forall proc eff impl. IvoryCall proc eff impl => Def proc -> impl
- indirect :: forall proc eff impl. IvoryCall proc eff impl => ProcPtr proc -> impl
- class IvoryCall proc eff impl | proc eff -> impl, impl -> eff where
- call_ :: forall proc eff impl. IvoryCall_ proc eff impl => Def proc -> impl
- indirect_ :: forall proc eff impl. IvoryCall_ proc eff impl => ProcPtr proc -> impl
- class IvoryCall_ proc eff impl | proc eff -> impl, impl -> eff where
- ret :: (GetReturn eff ~ Returns r, IvoryVar r) => r -> Ivory eff ()
- retVoid :: GetReturn eff ~ Returns () => Ivory eff ()
Documentation
class ProcType sig where Source #
Typeclass for procedure types, parametrized over the C procedure's signature, to produce a value representing their signature.
Procedure pointers
Procedure definitions.
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 '()'.
Body | |
|
class ProcType proc => IvoryProcDef proc impl | impl -> proc where Source #
Typeclass for an Ivory procedure definition to produce ; the type is parametrized over:
A variable name supply, and the typed values that have been generated.
Closure | |
|
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.
importProc :: forall proc. ProcType proc => Sym -> String -> Def proc Source #
Import a function from a C header.
newtype ImportFrom r Source #
ImportFrom | |
|
WrapIvory ImportFrom Source # | |
IvoryType ret => IvoryProcDef ((:->) * ([] *) ret) (ImportFrom ret) Source # | |
type Return ImportFrom Source # | |
importFrom :: String -> ImportFrom a Source #
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.
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, thenimpl
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 toimpl
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.
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
.