ivory-0.1.0.9: Safe embedded C programming.

Safe HaskellNone
LanguageHaskell2010

Ivory.Language.IBool

Synopsis

Documentation

newtype IBool Source #

Constructors

IBool 

Fields

Instances
IvoryExpr IBool Source # 
Instance details

Defined in Ivory.Language.IBool

Methods

wrapExpr :: Expr -> IBool Source #

IvoryVar IBool Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryType IBool Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryOrd IBool Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq IBool Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryStore IBool Source # 
Instance details

Defined in Ivory.Language.Ref

Ensures IBool Source # 
Instance details

Defined in Ivory.Language.Cond

Methods

ensures :: (WrapIvory m, IvoryVar r) => (r -> IBool) -> m r -> m r Source #

ensures_ :: WrapIvory m => IBool -> m () -> m () Source #

Requires IBool Source # 
Instance details

Defined in Ivory.Language.Cond

Methods

requires :: (WrapIvory m, IvoryType r) => IBool -> m r -> m r Source #

CheckStored IBool Source # 
Instance details

Defined in Ivory.Language.Cond

Methods

checkStored :: (IvoryVar a, IvoryRef ref, IvoryVar (ref s (Stored a))) => ref s (Stored a) -> (a -> IBool) -> Cond Source #

IvoryZeroVal IBool Source # 
Instance details

Defined in Ivory.Language.Init

IvoryInit IBool Source # 
Instance details

Defined in Ivory.Language.Init

Methods

ival :: IBool -> Init (Stored IBool) Source #

SafeCast IBool IChar Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

safeCast :: IBool -> IChar Source #

SafeCast IBool Sint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Sint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Sint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Sint8 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

safeCast :: IBool -> Sint8 Source #

SafeCast IBool Uint64 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Uint32 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Uint16 Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool Uint8 Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

safeCast :: IBool -> Uint8 Source #

SafeCast IBool IBool Source # 
Instance details

Defined in Ivory.Language.Cast

Methods

safeCast :: IBool -> IBool Source #

SafeCast IBool IDouble Source # 
Instance details

Defined in Ivory.Language.Cast

SafeCast IBool IFloat Source # 
Instance details

Defined in Ivory.Language.Cast

ifte_ :: IBool -> Ivory eff a -> Ivory eff b -> Ivory eff () Source #

If-then-else.

(?) :: IvoryExpr a => IBool -> (a, a) -> a Source #

Conditional expressions.

boolOp :: forall a. IvoryVar a => (Type -> ExpOp) -> a -> a -> IBool Source #

class IvoryExpr a => IvoryEq a where Source #

Minimal complete definition

Nothing

Methods

(==?) :: a -> a -> IBool infix 4 Source #

(/=?) :: a -> a -> IBool infix 4 Source #

Instances
IvoryEq Sint64 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq Sint32 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq Sint16 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq Sint8 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq Uint64 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq Uint32 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq Uint16 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq Uint8 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq IBool Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryEq IDouble Source # 
Instance details

Defined in Ivory.Language.Float

IvoryEq IFloat Source # 
Instance details

Defined in Ivory.Language.Float

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

Defined in Ivory.Language.Array

Methods

(==?) :: Ix n -> Ix n -> IBool Source #

(/=?) :: Ix n -> Ix n -> IBool Source #

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

Defined in Ivory.Language.BitData.Bits

Methods

(==?) :: Bits n -> Bits n -> IBool Source #

(/=?) :: Bits n -> Bits n -> IBool 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 #

class IvoryEq a => IvoryOrd a where Source #

Minimal complete definition

Nothing

Methods

(>?) :: a -> a -> IBool infix 4 Source #

(>=?) :: a -> a -> IBool infix 4 Source #

(<?) :: a -> a -> IBool infix 4 Source #

(<=?) :: a -> a -> IBool infix 4 Source #

Instances
IvoryOrd Sint64 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryOrd Sint32 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryOrd Sint16 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryOrd Sint8 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryOrd Uint64 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryOrd Uint32 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryOrd Uint16 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryOrd Uint8 Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryOrd IBool Source # 
Instance details

Defined in Ivory.Language.IBool

IvoryOrd IDouble Source # 
Instance details

Defined in Ivory.Language.Float

IvoryOrd IFloat Source # 
Instance details

Defined in Ivory.Language.Float

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

Defined in Ivory.Language.Array

Methods

(>?) :: Ix n -> Ix n -> IBool Source #

(>=?) :: Ix n -> Ix n -> IBool Source #

(<?) :: Ix n -> Ix n -> IBool Source #

(<=?) :: Ix n -> Ix n -> IBool Source #

(.&&) :: IBool -> IBool -> IBool infixr 3 Source #

(.||) :: IBool -> IBool -> IBool infixr 2 Source #