hxt-9.3.1.18: A collection of tools for processing XML with Haskell.

CopyrightCopyright (C) 2005 Uwe Schmidt
LicenseMIT
MaintainerUwe Schmidt (uwe\@fh-wedel.de)
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

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.

Synopsis

Documentation

data IfThen a b Source #

an auxiliary data type for choiceA

Constructors

a :-> b 

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.

Only ifA and orElse don't have default implementations

Minimal complete definition

ifA, orElse

Methods

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)

neg :: a b c -> a b b Source #

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

Instances
ArrowIf LA Source # 
Instance details

Defined in Control.Arrow.ListArrow

Methods

ifA :: LA b c -> LA b d -> LA b d -> LA b d Source #

ifP :: (b -> Bool) -> LA b d -> LA b d -> LA b d Source #

neg :: LA b c -> LA b b Source #

when :: LA b b -> LA b c -> LA b b Source #

whenP :: LA b b -> (b -> Bool) -> LA b b Source #

whenNot :: LA b b -> LA b c -> LA b b Source #

whenNotP :: LA b b -> (b -> Bool) -> LA b b Source #

guards :: LA b c -> LA b d -> LA b d Source #

guardsP :: (b -> Bool) -> LA b d -> LA b d Source #

filterA :: LA b c -> LA b b Source #

containing :: LA b c -> LA c d -> LA b c Source #

notContaining :: LA b c -> LA c d -> LA b c Source #

orElse :: LA b c -> LA b c -> LA b c Source #

choiceA :: [IfThen (LA b c) (LA b d)] -> LA b d Source #

tagA :: LA b c -> LA b (Either b b) Source #

spanA :: LA b b -> LA [b] ([b], [b]) Source #

partitionA :: LA b b -> LA [b] ([b], [b]) Source #

ArrowIf IOLA Source # 
Instance details

Defined in Control.Arrow.IOListArrow

Methods

ifA :: IOLA b c -> IOLA b d -> IOLA b d -> IOLA b d Source #

ifP :: (b -> Bool) -> IOLA b d -> IOLA b d -> IOLA b d Source #

neg :: IOLA b c -> IOLA b b Source #

when :: IOLA b b -> IOLA b c -> IOLA b b Source #

whenP :: IOLA b b -> (b -> Bool) -> IOLA b b Source #

whenNot :: IOLA b b -> IOLA b c -> IOLA b b Source #

whenNotP :: IOLA b b -> (b -> Bool) -> IOLA b b Source #

guards :: IOLA b c -> IOLA b d -> IOLA b d Source #

guardsP :: (b -> Bool) -> IOLA b d -> IOLA b d Source #

filterA :: IOLA b c -> IOLA b b Source #

containing :: IOLA b c -> IOLA c d -> IOLA b c Source #

notContaining :: IOLA b c -> IOLA c d -> IOLA b c Source #

orElse :: IOLA b c -> IOLA b c -> IOLA b c Source #

choiceA :: [IfThen (IOLA b c) (IOLA b d)] -> IOLA b d Source #

tagA :: IOLA b c -> IOLA b (Either b b) Source #

spanA :: IOLA b b -> IOLA [b] ([b], [b]) Source #

partitionA :: IOLA b b -> IOLA [b] ([b], [b]) Source #

ArrowIf (SLA s) Source # 
Instance details

Defined in Control.Arrow.StateListArrow

Methods

ifA :: SLA s b c -> SLA s b d -> SLA s b d -> SLA s b d Source #

ifP :: (b -> Bool) -> SLA s b d -> SLA s b d -> SLA s b d Source #

neg :: SLA s b c -> SLA s b b Source #

when :: SLA s b b -> SLA s b c -> SLA s b b Source #

whenP :: SLA s b b -> (b -> Bool) -> SLA s b b Source #

whenNot :: SLA s b b -> SLA s b c -> SLA s b b Source #

whenNotP :: SLA s b b -> (b -> Bool) -> SLA s b b Source #

guards :: SLA s b c -> SLA s b d -> SLA s b d Source #

guardsP :: (b -> Bool) -> SLA s b d -> SLA s b d Source #

filterA :: SLA s b c -> SLA s b b Source #

containing :: SLA s b c -> SLA s c d -> SLA s b c Source #

notContaining :: SLA s b c -> SLA s c d -> SLA s b c Source #

orElse :: SLA s b c -> SLA s b c -> SLA s b c Source #

choiceA :: [IfThen (SLA s b c) (SLA s b d)] -> SLA s b d Source #

tagA :: SLA s b c -> SLA s b (Either b b) Source #

spanA :: SLA s b b -> SLA s [b] ([b], [b]) Source #

partitionA :: SLA s b b -> SLA s [b] ([b], [b]) Source #

ArrowIf (IOSLA s) Source # 
Instance details

Defined in Control.Arrow.IOStateListArrow

Methods

ifA :: IOSLA s b c -> IOSLA s b d -> IOSLA s b d -> IOSLA s b d Source #

ifP :: (b -> Bool) -> IOSLA s b d -> IOSLA s b d -> IOSLA s b d Source #

neg :: IOSLA s b c -> IOSLA s b b Source #

when :: IOSLA s b b -> IOSLA s b c -> IOSLA s b b Source #

whenP :: IOSLA s b b -> (b -> Bool) -> IOSLA s b b Source #

whenNot :: IOSLA s b b -> IOSLA s b c -> IOSLA s b b Source #

whenNotP :: IOSLA s b b -> (b -> Bool) -> IOSLA s b b Source #

guards :: IOSLA s b c -> IOSLA s b d -> IOSLA s b d Source #

guardsP :: (b -> Bool) -> IOSLA s b d -> IOSLA s b d Source #

filterA :: IOSLA s b c -> IOSLA s b b Source #

containing :: IOSLA s b c -> IOSLA s c d -> IOSLA s b c Source #

notContaining :: IOSLA s b c -> IOSLA s c d -> IOSLA s b c Source #

orElse :: IOSLA s b c -> IOSLA s b c -> IOSLA s b c Source #

choiceA :: [IfThen (IOSLA s b c) (IOSLA s b d)] -> IOSLA s b d Source #

tagA :: IOSLA s b c -> IOSLA s b (Either b b) Source #

spanA :: IOSLA s b b -> IOSLA s [b] ([b], [b]) Source #

partitionA :: IOSLA s b b -> IOSLA s [b] ([b], [b]) Source #