cond-0.5.1: Basic conditional and boolean operators with monadic variants.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Conditional

Description

A convenient set of useful conditional operators.

Synopsis

Conversion typeclass

class ToBool bool where Source #

Conversion of values to Bool.

Instances of ToBool that are also Boolean should obey the following laws:

p || q = if toBool p then true else q
p && q = if toBool p then q else false

Methods

toBool :: bool -> Bool Source #

Instances

Instances details
ToBool All Source # 
Instance details

Defined in Control.Conditional

Methods

toBool :: All -> Bool Source #

ToBool Any Source # 
Instance details

Defined in Control.Conditional

Methods

toBool :: Any -> Bool Source #

ToBool Bool Source # 
Instance details

Defined in Control.Conditional

Methods

toBool :: Bool -> Bool Source #

ToBool (Dual Bool) Source # 
Instance details

Defined in Control.Conditional

Methods

toBool :: Dual Bool -> Bool Source #

Basic conditional operators

if' :: ToBool bool => bool -> a -> a -> a Source #

A simple conditional operator

(??) :: ToBool bool => a -> a -> bool -> a infixr 1 Source #

if' with the Bool argument at the end (infixr 1).

bool :: ToBool bool => a -> a -> bool -> a Source #

A catamorphism (aka fold) for booleans. This is analogous to foldr, maybe, and either. The first argument is the false case, the second argument is the true case, and the last argument is the predicate value.

ifM :: (ToBool bool, Monad m) => m bool -> m a -> m a -> m a Source #

if' lifted to Monad. Unlike liftM3 if', this is short-circuiting in the monad, such that only the predicate action and one of the remaining argument actions are executed.

(<||>) :: (ToBool bool, Boolean bool, Monad m) => m bool -> m bool -> m bool infixr 2 Source #

Lifted inclusive disjunction. Unlike liftM2 (||), This function is short-circuiting in the monad. Fixity is the same as || (infixr 2).

(<&&>) :: (ToBool bool, Boolean bool, Monad m) => m bool -> m bool -> m bool infixr 3 Source #

Lifted conjunction. Unlike liftM2 (&&), this function is short-circuiting in the monad. Fixity is the same as && (infxr 3).

notM :: (Boolean bool, Monad m) => m bool -> m bool Source #

Lifted boolean negation.

xorM :: (Boolean bool, Monad m) => m bool -> m bool -> m bool Source #

Lifted boolean exclusive disjunction.

Lisp-style conditional operators

cond :: ToBool bool => [(bool, a)] -> a Source #

Lisp-style conditionals. If no conditions match, then a runtime exception is thrown. Here's a trivial example:

  signum x = cond [(x > 0     , 1 )
                  ,(x < 0     , -1)
                  ,(otherwise , 0 )]

condDefault :: ToBool bool => a -> [(bool, a)] -> a Source #

Analogous to the cond function with a default value supplied, which will be used when no condition in the list is matched.

condPlus :: (ToBool bool, MonadPlus m) => [(bool, a)] -> m a Source #

Lisp-style conditionals generalized over MonadPlus. If no conditions match, then the result is mzero. This is a safer variant of cond.

Here's a highly contrived example using fromMaybe:

  signum x = fromMaybe 0 . condPlus $ [(x > 0, 1 ) 
                                      ,(x < 0, -1)]

Alternatively, you could use the <| operator from Hoare's ternary conditional choice operator, like so:

  signum x = 0 <| condPlus [(x > 0, 1 ) 
                           ,(x < 0, -1)]

condM :: (ToBool bool, Monad m) => [(m bool, m a)] -> m a Source #

cond lifted to Monad. If no conditions match, a runtime exception is thrown.

condPlusM :: (ToBool bool, MonadPlus m) => [(m bool, m a)] -> m a Source #

condPlus lifted to Monad. If no conditions match, then mzero is returned.

otherwiseM :: (Boolean bool, Monad m) => m bool Source #

A synonym for return true.

Conditional operator on categories

(?.) :: (ToBool bool, Category cat) => bool -> cat a a -> cat a a infixr 9 Source #

Conditional composition. If the predicate is False, id is returned instead of the second argument. This function, for example, can be used to conditionally add functions to a composition chain.

Conditional operator on monoids

(?<>) :: (ToBool bool, Monoid a) => bool -> a -> a infixr 7 Source #

Conditional monoid operator. If the predicate is False, the second argument is replaced with mempty. The fixity of this operator is one level higher than <>.

It can also be used to chain multiple predicates together, like this:

even (length ls) ?<> not (null ls) ?<> ls

Conditional operator on functions

select :: ToBool bool => (a -> bool) -> (a -> b) -> (a -> b) -> a -> b Source #

Composes a predicate function and 2 functions into a single function. The first function is called when the predicate yields True, the second when the predicate yields False.

Note that after importing Control.Monad.Instances, select becomes a special case of ifM.

selectM :: (ToBool bool, Monad m) => (a -> m bool) -> (a -> m b) -> (a -> m b) -> a -> m b Source #

select lifted to Monad.

C-style ternary conditional

(?) :: b -> (b -> a) -> a infixr 0 Source #

An operator that allows you to write C-style ternary conditionals of the form:

p ? t ?? f

Note that parentheses are required in order to chain sequences of conditionals together. This is probably a good thing.

Hoare's conditional choice operator

The following operators form a ternary conditional of the form

t <| p |> f

These operators chain with right associative fixity. This allows chaining of conditions, where the result of the expression is the value to the left of the first predicate that succeeds.

For more information see http://zenzike.com/posts/2011-08-01-the-conditional-choice-operator

(|>) :: ToBool bool => bool -> a -> Maybe a infixr 0 Source #

Right bracket of the conditional choice operator. If the predicate is True, returns Nothing, otherwise it returns Just the right-hand argument.

(<|) :: a -> Maybe a -> a infixr 0 Source #

Left bracket of the conditional choice operator. This is equivalent to fromMaybe

Lifted conditional choice

In addition, you can write lifted conditionals of the form:

t <<| p |>> f

(|>>) :: (ToBool bool, Monad m) => m bool -> m a -> m (Maybe a) infixr 0 Source #

A monadic variant of |>.

(<<|) :: Monad m => m a -> m (Maybe a) -> m a infixr 0 Source #

A monadic variant of <|.

Unicode variants

Intended to resemble the notation used in Tony Hoare's Unified Theories of Programming.

(⊳) :: ToBool bool => bool -> a -> Maybe a infixr 0 Source #

Unicode rebinding of |>.

(⊲) :: a -> Maybe a -> a infixr 0 Source #

Unicode rebinding of <|.

Generalized monadic conditionals

guard :: (ToBool bool, MonadPlus m) => bool -> m () Source #

Generalization of guard

guardM :: (ToBool bool, MonadPlus m) => m bool -> m () Source #

A variant of guard with a monadic predicate.

when :: (ToBool bool, Monad m) => bool -> m () -> m () Source #

Generalization of when

whenM :: (ToBool bool, Monad m) => m bool -> m () -> m () Source #

A variant of when with a monadic predicate.

unless :: (Boolean bool, ToBool bool, Monad m) => bool -> m () -> m () Source #

Generalization of unless

unlessM :: (ToBool bool, Boolean bool, Monad m) => m bool -> m () -> m () Source #

A variant of unless with a monadic predicate.