ivory-0.1.0.8: Safe embedded C programming.

Safe HaskellNone
LanguageHaskell2010

Ivory.Language.Type

Synopsis

Documentation

class IvoryType t where Source #

The connection between Haskell and Ivory types.

Minimal complete definition

ivoryType

Methods

ivoryType :: Proxy t -> Type Source #

Instances
IvoryType () Source #

void type

Instance details

Defined in Ivory.Language.Type

Methods

ivoryType :: Proxy () -> Type Source #

IvoryType OpaqueType Source # 
Instance details

Defined in Ivory.Language.Type

IvoryType IString Source # 
Instance details

Defined in Ivory.Language.IString

IvoryType IChar Source # 
Instance details

Defined in Ivory.Language.IChar

IvoryType Sint64 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryType Sint32 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryType Sint16 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryType Sint8 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryType Uint64 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryType Uint32 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryType Uint16 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryType Uint8 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryType IBool Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryType IDouble Source # 
Instance details

Defined in Ivory.Language.Float

IvoryType IFloat Source # 
Instance details

Defined in Ivory.Language.Float

ProcType proc => IvoryType (Def proc) Source # 
Instance details

Defined in Ivory.Language.Proc

Methods

ivoryType :: Proxy (Def proc) -> Type Source #

ProcType proc => IvoryType (ProcPtr proc) Source # 
Instance details

Defined in Ivory.Language.Proc

Methods

ivoryType :: Proxy (ProcPtr proc) -> Type Source #

ANat n => IvoryType (Ix n) Source # 
Instance details

Defined in Ivory.Language.Array

Methods

ivoryType :: Proxy (Ix n) -> Type Source #

IvoryRep (BitRep n) => IvoryType (Bits n) Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

Methods

ivoryType :: Proxy (Bits n) -> Type Source #

(KnownNullability n, KnownConstancy c, IvoryArea a) => IvoryType (Pointer n c s a) Source # 
Instance details

Defined in Ivory.Language.Pointer

Methods

ivoryType :: Proxy (Pointer n c s a) -> Type Source #

class IvoryType t => IvoryVar t where Source #

Lifting a variable name.

Minimal complete definition

wrapVar, unwrapExpr

Methods

wrapVar :: Var -> t Source #

unwrapExpr :: t -> Expr Source #

Instances
IvoryVar IString Source # 
Instance details

Defined in Ivory.Language.IString

IvoryVar IChar Source # 
Instance details

Defined in Ivory.Language.IChar

IvoryVar Sint64 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryVar Sint32 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryVar Sint16 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryVar Sint8 Source # 
Instance details

Defined in Ivory.Language.Sint

IvoryVar Uint64 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryVar Uint32 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryVar Uint16 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryVar Uint8 Source # 
Instance details

Defined in Ivory.Language.Uint

IvoryVar IBool Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryVar IDouble Source # 
Instance details

Defined in Ivory.Language.Float

IvoryVar IFloat Source # 
Instance details

Defined in Ivory.Language.Float

ProcType proc => IvoryVar (ProcPtr proc) Source # 
Instance details

Defined in Ivory.Language.Proc

Methods

wrapVar :: Var -> ProcPtr proc Source #

unwrapExpr :: ProcPtr proc -> Expr Source #

ANat n => IvoryVar (Ix n) Source # 
Instance details

Defined in Ivory.Language.Array

Methods

wrapVar :: Var -> Ix n Source #

unwrapExpr :: Ix n -> Expr Source #

IvoryRep (BitRep n) => IvoryVar (Bits n) Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

Methods

wrapVar :: Var -> Bits n Source #

unwrapExpr :: Bits n -> Expr Source #

(KnownNullability n, KnownConstancy c, IvoryArea a) => IvoryVar (Pointer n c s a) Source # 
Instance details

Defined in Ivory.Language.Pointer

Methods

wrapVar :: Var -> Pointer n c s a Source #

unwrapExpr :: Pointer n c s a -> Expr Source #

class IvoryVar t => IvoryExpr t where Source #

Unwrapping for Ivory expressions.

Minimal complete definition

wrapExpr

Methods

wrapExpr :: Expr -> t Source #

Instances
IvoryExpr IString Source # 
Instance details

Defined in Ivory.Language.IString

IvoryExpr IChar Source # 
Instance details

Defined in Ivory.Language.IChar

Methods

wrapExpr :: Expr -> IChar Source #

IvoryExpr Sint64 Source # 
Instance details

Defined in Ivory.Language.Sint

Methods

wrapExpr :: Expr -> Sint64 Source #

IvoryExpr Sint32 Source # 
Instance details

Defined in Ivory.Language.Sint

Methods

wrapExpr :: Expr -> Sint32 Source #

IvoryExpr Sint16 Source # 
Instance details

Defined in Ivory.Language.Sint

Methods

wrapExpr :: Expr -> Sint16 Source #

IvoryExpr Sint8 Source # 
Instance details

Defined in Ivory.Language.Sint

Methods

wrapExpr :: Expr -> Sint8 Source #

IvoryExpr Uint64 Source # 
Instance details

Defined in Ivory.Language.Uint

Methods

wrapExpr :: Expr -> Uint64 Source #

IvoryExpr Uint32 Source # 
Instance details

Defined in Ivory.Language.Uint

Methods

wrapExpr :: Expr -> Uint32 Source #

IvoryExpr Uint16 Source # 
Instance details

Defined in Ivory.Language.Uint

Methods

wrapExpr :: Expr -> Uint16 Source #

IvoryExpr Uint8 Source # 
Instance details

Defined in Ivory.Language.Uint

Methods

wrapExpr :: Expr -> Uint8 Source #

IvoryExpr IBool Source # 
Instance details

Defined in Ivory.Language.IBool

Methods

wrapExpr :: Expr -> IBool Source #

IvoryExpr IDouble Source # 
Instance details

Defined in Ivory.Language.Float

IvoryExpr IFloat Source # 
Instance details

Defined in Ivory.Language.Float

Methods

wrapExpr :: Expr -> IFloat Source #

ANat n => IvoryExpr (Ix n) Source # 
Instance details

Defined in Ivory.Language.Array

Methods

wrapExpr :: Expr -> Ix n Source #

IvoryRep (BitRep n) => IvoryExpr (Bits n) Source # 
Instance details

Defined in Ivory.Language.BitData.Bits

Methods

wrapExpr :: Expr -> Bits n Source #

(KnownNullability n, KnownConstancy c, IvoryArea a) => IvoryExpr (Pointer n c s a) Source # 
Instance details

Defined in Ivory.Language.Pointer

Methods

wrapExpr :: Expr -> Pointer n c s a Source #

typedExpr :: forall t. IvoryVar t => t -> Typed Expr Source #

exprBinop :: IvoryExpr a => (Expr -> Expr -> Expr) -> a -> a -> a Source #

exprUnary :: IvoryExpr a => (Expr -> Expr) -> a -> a Source #

data OpaqueType Source #

An opaque type that can never be implemented.

Constructors

OpaqueType 
Instances
IvoryType OpaqueType Source # 
Instance details

Defined in Ivory.Language.Type