Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
A convenient set of useful conditional operators.
Synopsis
- class ToBool bool where
- if' :: ToBool bool => bool -> a -> a -> a
- (??) :: ToBool bool => a -> a -> bool -> a
- bool :: ToBool bool => a -> a -> bool -> a
- ifM :: (ToBool bool, Monad m) => m bool -> m a -> m a -> m a
- (<||>) :: (ToBool bool, Boolean bool, Monad m) => m bool -> m bool -> m bool
- (<&&>) :: (ToBool bool, Boolean bool, Monad m) => m bool -> m bool -> m bool
- notM :: (Boolean bool, Monad m) => m bool -> m bool
- xorM :: (Boolean bool, Monad m) => m bool -> m bool -> m bool
- cond :: ToBool bool => [(bool, a)] -> a
- condDefault :: ToBool bool => a -> [(bool, a)] -> a
- condPlus :: (ToBool bool, MonadPlus m) => [(bool, a)] -> m a
- condM :: (ToBool bool, Monad m) => [(m bool, m a)] -> m a
- condPlusM :: (ToBool bool, MonadPlus m) => [(m bool, m a)] -> m a
- otherwiseM :: (Boolean bool, Monad m) => m bool
- (?.) :: (ToBool bool, Category cat) => bool -> cat a a -> cat a a
- (?<>) :: (ToBool bool, Monoid a) => bool -> a -> a
- select :: ToBool bool => (a -> bool) -> (a -> b) -> (a -> b) -> a -> b
- selectM :: (ToBool bool, Monad m) => (a -> m bool) -> (a -> m b) -> (a -> m b) -> a -> m b
- (?) :: b -> (b -> a) -> a
- (|>) :: ToBool bool => bool -> a -> Maybe a
- (<|) :: a -> Maybe a -> a
- (|>>) :: (ToBool bool, Monad m) => m bool -> m a -> m (Maybe a)
- (<<|) :: Monad m => m a -> m (Maybe a) -> m a
- (⊳) :: ToBool bool => bool -> a -> Maybe a
- (⊲) :: a -> Maybe a -> a
- guard :: (ToBool bool, MonadPlus m) => bool -> m ()
- guardM :: (ToBool bool, MonadPlus m) => m bool -> m ()
- when :: (ToBool bool, Monad m) => bool -> m () -> m ()
- whenM :: (ToBool bool, Monad m) => m bool -> m () -> m ()
- unless :: (Boolean bool, ToBool bool, Monad m) => bool -> m () -> m ()
- unlessM :: (ToBool bool, Boolean bool, Monad m) => m bool -> m () -> m ()
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
Basic conditional operators
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)]
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
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
.
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
(<|) :: 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 |>
.
Unicode variants
Intended to resemble the notation used in Tony Hoare's Unified Theories of Programming.
Generalized monadic conditionals
guardM :: (ToBool bool, MonadPlus m) => m bool -> m () Source #
A variant of guard
with a monadic predicate.
whenM :: (ToBool bool, Monad m) => m bool -> m () -> m () Source #
A variant of when
with a monadic predicate.