ivory-0.1.0.9: Safe embedded C programming.

Safe HaskellNone
LanguageHaskell2010

Ivory.Language.Pointer

Description

Generic pointer

Synopsis

Documentation

data Constancy Source #

Constructors

Const

data may not be modified

Mutable

data may be modified

class KnownConstancy (c :: Constancy) Source #

Minimal complete definition

demoteConstancy

data Nullability Source #

Constructors

Nullable

may be NULL

Valid

may not be NULL

data Pointer (n :: Nullability) (c :: Constancy) (s :: RefScope) (a :: Area *) Source #

Constructors

Pointer 

Fields

Instances
IvoryAddrOf ConstMemArea ConstRef Source # 
Instance details

Defined in Ivory.Language.MemArea

Methods

addrOf :: IvoryArea area => ConstMemArea area -> ConstRef Global area Source #

IvoryAddrOf MemArea Ref Source # 
Instance details

Defined in Ivory.Language.MemArea

Methods

addrOf :: IvoryArea area => MemArea area -> Ref Global area Source #

IvoryRef (Pointer Valid c) Source # 
Instance details

Defined in Ivory.Language.Ref

Methods

unwrapRef :: IvoryVar a => Pointer Valid c s (Stored a) -> Expr

IvoryArea area => IvoryZeroVal (Ptr Global area) Source # 
Instance details

Defined in Ivory.Language.Init

Methods

izeroval :: Init (Stored (Ptr Global area)) Source #

IvoryArea area => IvoryInit (Ptr Global area) Source # 
Instance details

Defined in Ivory.Language.Init

Methods

ival :: Ptr Global area -> Init (Stored (Ptr Global area)) 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 #

(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 #

(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 #

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

Defined in Ivory.Language.Pointer

Methods

(==?) :: Pointer n c s a -> Pointer n c s a -> IBool Source #

(/=?) :: Pointer n c s a -> Pointer n c s a -> IBool Source #

(KnownConstancy c, IvoryArea a) => IvoryStore (Pointer Nullable c Global a) Source # 
Instance details

Defined in Ivory.Language.Ref

pointerCast :: forall (s :: RefScope) (a :: Area *). (PointerCast n1 c1 n2 c2, IvoryArea a) => Pointer n1 c1 s a -> Pointer n2 c2 s a Source #

pointerCastToConst :: (KnownNullability n, IvoryArea a) => Pointer n Mutable s a -> Pointer n Const s a Source #

unsafePointerCast :: (KnownNullability n1, KnownNullability n2, KnownConstancy c1, KnownConstancy c2, IvoryArea a) => Pointer n1 c1 s a -> Pointer n2 c2 s a Source #

withRef :: (KnownConstancy c, IvoryArea a) => Pointer Nullable c s a -> (Pointer Valid c s a -> Ivory eff t) -> Ivory eff f -> Ivory eff () Source #

Unwrap a pointer, and use it as a reference.