ifA :: a b c -> a b d -> a b d -> a b d | Source |
|
if lifted to arrows
|
|
ifP :: (b -> Bool) -> a b d -> a b d -> a b d | Source |
|
shortcut: ifP p = ifA (isA p)
|
|
|
negation: neg f = ifA f none this
|
|
when :: a b b -> a b c -> a b b | Source |
|
f `when` g : when the predicate g holds, f is applied, else the identity filter this
|
|
|
shortcut: f `whenP` p = f `when` (isA p)
|
|
whenNot :: a b b -> a b c -> a b b | Source |
|
f `whenNot` g : when the predicate g does not hold, f is applied, else the identity filter this
|
|
|
like whenP
|
|
guards :: a b c -> a b d -> a b d | Source |
|
g `guards` f : when the predicate g holds, f is applied, else none
|
|
|
like whenP
|
|
containing :: a b c -> a c d -> a b c | Source |
|
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 c | Source |
|
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 c | Source |
|
f `orElse` g : directional choice: if f succeeds, the result of f is the result, else g is applied
|
|
|
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 ]
|
|
|
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
|