| Portability | portable | 
|---|---|
| Stability | experimental | 
| Maintainer | Uwe Schmidt (uwe\@fh-wedel.de) | 
Control.Arrow.ArrowIf
Description
Conditionals for List Arrows
This module defines conditional combinators for list arrows.
The empty list as result represents False, none empty lists True.
- class ArrowList a => ArrowIf a  where
- ifA :: a b c -> a b d -> a b d -> a b d
 - ifP :: (b -> Bool) -> a b d -> a b d -> a b d
 - neg :: a b c -> a b b
 - when :: a b b -> a b c -> a b b
 - whenP :: a b b -> (b -> Bool) -> a b b
 - whenNot :: a b b -> a b c -> a b b
 - whenNotP :: a b b -> (b -> Bool) -> a b b
 - guards :: a b c -> a b d -> a b d
 - guardsP :: (b -> Bool) -> a b d -> a b d
 - filterA :: a b c -> a b b
 - containing :: a b c -> a c d -> a b c
 - notContaining :: a b c -> a c d -> a b c
 - orElse :: a b c -> a b c -> a b c
 - choiceA :: [IfThen (a b c) (a b d)] -> a b d
 - tagA :: a b c -> a b (Either b b)
 - spanA :: a b b -> a [b] ([b], [b])
 - partitionA :: a b b -> a [b] ([b], [b])
 
 - data IfThen a b = a :-> b
 
Documentation
class ArrowList a => ArrowIf a whereSource
The interface for arrows as conditionals.
Requires list arrows because False is represented as empty list, True as none empty lists.
Methods
ifA :: a b c -> a b d -> a b d -> a b dSource
if lifted to arrows
ifP :: (b -> Bool) -> a b d -> a b d -> a b dSource
shortcut:  ifP p = ifA (isA p) 
negation:  neg f = ifA f none this 
when :: a b b -> a b c -> a b bSource
 f `when` g  : when the predicate g holds, f is applied, else the identity filter this
whenP :: a b b -> (b -> Bool) -> a b bSource
shortcut:  f `whenP` p = f `when` (isA p) 
whenNot :: a b b -> a b c -> a b bSource
 f `whenNot` g  : when the predicate g does not hold, f is applied, else the identity filter this
whenNotP :: a b b -> (b -> Bool) -> a b bSource
like whenP
guards :: a b c -> a b d -> a b dSource
 g `guards` f  : when the predicate g holds, f is applied, else none
guardsP :: (b -> Bool) -> a b d -> a b dSource
like whenP
filterA :: a b c -> a b bSource
shortcut for  f 
guards this 
containing :: a b c -> a c d -> a b cSource
 f `containing` g  : keep only those results from f for which g holds
definition:  f `containing` g = f >>> g `guards` this 
notContaining :: a b c -> a c d -> a b cSource
 f `notContaining` g  : keep only those results from f for which g does not hold
definition:  f `notContaining` g = f >>> ifA g none this 
orElse :: a b c -> a b c -> a b cSource
 f `orElse` g  : directional choice: if f succeeds, the result of f is the result, else g is applied
choiceA :: [IfThen (a b c) (a b d)] -> a b dSource
generalisation of orElse for multi way branches like in case expressions.
An auxiliary data type IfThen with an infix constructor :-> is used for writing multi way branches
example:  choiceA [ p1 :-> e1, p2 :-> e2, this :-> default ] 
tagA :: a b c -> a b (Either b b)Source
tag a value with Left or Right, if arrow has success, input is tagged with Left, else with Right
spanA :: a b b -> a [b] ([b], [b])Source
split a list value with an arrow and returns a pair of lists.
 This is the arrow version of span. The arrow is deterministic.
example:  runLA (spanA (isA (/= '-'))) "abc-def"  gives  [("abc","-def")]  as result
partitionA :: a b b -> a [b] ([b], [b])Source
partition a list of values into a pair of lists
This is the arrow Version of partition