ivory-0.1.0.7: Safe embedded C programming.

Safe HaskellNone
LanguageHaskell2010

Ivory.Language.Cond

Synopsis

Documentation

emitPreCond :: Require -> Ivory eff () Source #

Emit a pre-condition.

XXX do not export

emitPostCond :: Ensure -> Ivory eff () Source #

Emit a post-condition.

XXX do not export

newtype Cond Source #

Constructors

Cond 

Fields

  • runCond :: forall eff. Ivory eff Cond

    Use the naming environment from the Ivory monad.

Instances

Ensures Cond Source # 

Methods

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

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

Requires Cond Source # 

Methods

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

CheckStored Cond Source # 

Methods

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

check :: IBool -> Cond Source #

Checkable a boolean expression.

checkStored' :: forall ref s a c. (CheckStored c, IvoryVar a, IvoryRef ref, IvoryVar (ref s (Stored a))) => (c -> Cond) -> ref s (Stored a) -> (a -> c) -> Cond Source #

class CheckStored c where Source #

Minimal complete definition

checkStored

Methods

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

Instances

CheckStored IBool Source # 

Methods

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

CheckStored Cond Source # 

Methods

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

class Requires c where Source #

Proc bodies that have pre-conditions. Multiple pre-conditions may be provided, for which the conjunction must hold.

Minimal complete definition

requires

Methods

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

Instances

Requires IBool Source # 

Methods

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

Requires Cond Source # 

Methods

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

requires' :: (WrapIvory m, Requires c, IvoryType r) => (c -> Cond) -> c -> m r -> m r Source #

class Ensures c where Source #

Proc bodies that have post-conditions. Multiple post-conditions may be provided, for which the conjunction must hold.

Minimal complete definition

ensures, ensures_

Methods

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

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

Instances

Ensures IBool Source # 

Methods

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

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

Ensures Cond Source # 

Methods

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

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

ensures' :: (WrapIvory m, Ensures c, IvoryVar r) => (c -> Cond) -> (r -> c) -> m r -> m r Source #

ensures_' :: (WrapIvory m, Ensures c) => (c -> Cond) -> c -> m () -> m () Source #