Copyright | Copyright (C) 2005 Uwe Schmidt |
---|---|
License | MIT |
Maintainer | Uwe Schmidt (uwe\@fh-wedel.de) |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell98 |
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 where Source
The interface for arrows as conditionals.
Requires list arrows because False is represented as empty list, True as none empty lists.
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
whenP :: a b b -> (b -> Bool) -> a b b Source
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
whenNotP :: a b b -> (b -> Bool) -> a b b Source
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
guardsP :: (b -> Bool) -> a b d -> a b d Source
like whenP
filterA :: a b c -> a b b Source
shortcut for f
guards
this
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
choiceA :: [IfThen (a b c) (a b d)] -> a b d Source
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