base-4.6.0.0: Basic libraries

Portabilityportable
Stabilityprovisional
Maintainerlibraries@haskell.org
Safe HaskellTrustworthy

Control.Arrow

Contents

Description

Basic arrow definitions, based on * Generalising Monads to Arrows, by John Hughes, Science of Computer Programming 37, pp67-111, May 2000. plus a couple of definitions (returnA and loop) from * A New Notation for Arrows, by Ross Paterson, in ICFP 2001, Firenze, Italy, pp229-240. These papers and more information on arrows can be found at http://www.haskell.org/arrows/.

Synopsis

Arrows

class Category a => Arrow a whereSource

The basic arrow class.

Minimal complete definition: arr and first, satisfying the laws

where

 assoc ((a,b),c) = (a,(b,c))

The other combinators have sensible default definitions, which may be overridden for efficiency.

Methods

arr :: (b -> c) -> a b cSource

Lift a function to an arrow.

first :: a b c -> a (b, d) (c, d)Source

Send the first component of the input through the argument arrow, and copy the rest unchanged to the output.

second :: a b c -> a (d, b) (d, c)Source

A mirror image of first.

The default definition may be overridden with a more efficient version if desired.

(***) :: a b c -> a b' c' -> a (b, b') (c, c')Source

Split the input between the two argument arrows and combine their output. Note that this is in general not a functor.

The default definition may be overridden with a more efficient version if desired.

(&&&) :: a b c -> a b c' -> a b (c, c')Source

Fanout: send the input to both argument arrows and combine their output.

The default definition may be overridden with a more efficient version if desired.

Instances

Arrow (->) 
(Category (Kleisli m), Monad m) => Arrow (Kleisli m) 

newtype Kleisli m a b Source

Kleisli arrows of a monad.

Constructors

Kleisli 

Fields

runKleisli :: a -> m b
 

Instances

Monad m => Category (Kleisli m) 
(Arrow (Kleisli m), MonadFix m) => ArrowLoop (Kleisli m)

Beware that for many monads (those for which the >>= operation is strict) this instance will not satisfy the right-tightening law required by the ArrowLoop class.

(Arrow (Kleisli m), Monad m) => ArrowApply (Kleisli m) 
(Arrow (Kleisli m), Monad m) => ArrowChoice (Kleisli m) 
(ArrowZero (Kleisli m), MonadPlus m) => ArrowPlus (Kleisli m) 
(Arrow (Kleisli m), MonadPlus m) => ArrowZero (Kleisli m) 
(Category (Kleisli m), Monad m) => Arrow (Kleisli m) 

Derived combinators

returnA :: Arrow a => a b bSource

The identity arrow, which plays the role of return in arrow notation.

(^>>) :: Arrow a => (b -> c) -> a c d -> a b dSource

Precomposition with a pure function.

(>>^) :: Arrow a => a b c -> (c -> d) -> a b dSource

Postcomposition with a pure function.

(>>>) :: Category cat => cat a b -> cat b c -> cat a cSource

Left-to-right composition

(<<<) :: Category cat => cat b c -> cat a b -> cat a cSource

Right-to-left composition

Right-to-left variants

(<<^) :: Arrow a => a c d -> (b -> c) -> a b dSource

Precomposition with a pure function (right-to-left variant).

(^<<) :: Arrow a => (c -> d) -> a b c -> a b dSource

Postcomposition with a pure function (right-to-left variant).

Monoid operations

class Arrow a => ArrowZero a whereSource

Methods

zeroArrow :: a b cSource

Instances

class ArrowZero a => ArrowPlus a whereSource

A monoid on arrows.

Methods

(<+>) :: a b c -> a b c -> a b cSource

An associative operation with identity zeroArrow.

Instances

Conditionals

class Arrow a => ArrowChoice a whereSource

Choice, for arrows that support it. This class underlies the if and case constructs in arrow notation. Minimal complete definition: left, satisfying the laws

where

 assocsum (Left (Left x)) = Left x
 assocsum (Left (Right y)) = Right (Left y)
 assocsum (Right z) = Right (Right z)

The other combinators have sensible default definitions, which may be overridden for efficiency.

Methods

left :: a b c -> a (Either b d) (Either c d)Source

Feed marked inputs through the argument arrow, passing the rest through unchanged to the output.

right :: a b c -> a (Either d b) (Either d c)Source

A mirror image of left.

The default definition may be overridden with a more efficient version if desired.

(+++) :: a b c -> a b' c' -> a (Either b b') (Either c c')Source

Split the input between the two argument arrows, retagging and merging their outputs. Note that this is in general not a functor.

The default definition may be overridden with a more efficient version if desired.

(|||) :: a b d -> a c d -> a (Either b c) dSource

Fanin: Split the input between the two argument arrows and merge their outputs.

The default definition may be overridden with a more efficient version if desired.

Instances

Arrow application

class Arrow a => ArrowApply a whereSource

Some arrows allow application of arrow inputs to other inputs. Instances should satisfy the following laws:

Such arrows are equivalent to monads (see ArrowMonad).

Methods

app :: a (a b c, b) cSource

Instances

newtype ArrowMonad a b Source

The ArrowApply class is equivalent to Monad: any monad gives rise to a Kleisli arrow, and any instance of ArrowApply defines a monad.

Constructors

ArrowMonad (a () b) 

leftApp :: ArrowApply a => a b c -> a (Either b d) (Either c d)Source

Any instance of ArrowApply can be made into an instance of ArrowChoice by defining left = leftApp.

Feedback

class Arrow a => ArrowLoop a whereSource

The loop operator expresses computations in which an output value is fed back as input, although the computation occurs only once. It underlies the rec value recursion construct in arrow notation. loop should satisfy the following laws:

extension
loop (arr f) = arr (\ b -> fst (fix (\ (c,d) -> f (b,d))))
left tightening
loop (first h >>> f) = h >>> loop f
right tightening
loop (f >>> first h) = loop f >>> h
sliding
loop (f >>> arr (id *** k)) = loop (arr (id *** k) >>> f)
vanishing
loop (loop f) = loop (arr unassoc >>> f >>> arr assoc)
superposing
second (loop f) = loop (arr assoc >>> second f >>> arr unassoc)

where

 assoc ((a,b),c) = (a,(b,c))
 unassoc (a,(b,c)) = ((a,b),c)

Methods

loop :: a (b, d) (c, d) -> a b cSource

Instances

ArrowLoop (->) 
(Arrow (Kleisli m), MonadFix m) => ArrowLoop (Kleisli m)

Beware that for many monads (those for which the >>= operation is strict) this instance will not satisfy the right-tightening law required by the ArrowLoop class.