Haskell Core Libraries (base package)ParentContentsIndex
Control.Arrow
Portability portable
Stability experimental
Maintainer ross@soi.city.ac.uk
Contents
Arrows
Derived combinators
Monoid operations
Conditionals
Arrow application
Feedback
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. See these papers for the equations these combinators are expected to satisfy. These papers and more information on arrows can be found at http://www.haskell.org/arrows/.
Synopsis
class Arrow a where
(&&&) :: a b c -> a b c' -> a b (c, c')
(***) :: a b c -> a b' c' -> a (b, b') (c, c')
second :: a b c -> a (d, b) (d, c)
first :: a b c -> a (b, d) (c, d)
(>>>) :: a b c -> a c d -> a b d
pure :: (b -> c) -> a b c
arr :: (b -> c) -> a b c
data Kleisli m a b = Kleisli (a -> m b)
returnA :: (Arrow a) => a b b
(<<<) :: (Arrow a) => a c d -> a b c -> a b d
class (Arrow a) => ArrowZero a where
zeroArrow :: a b c
class (ArrowZero a) => ArrowPlus a where
(<+>) :: a b c -> a b c -> a b c
class (Arrow a) => ArrowChoice a where
(|||) :: a b d -> a c d -> a (Either b c) d
(+++) :: a b c -> a b' c' -> a (Either b b') (Either c c')
right :: a b c -> a (Either d b) (Either d c)
left :: a b c -> a (Either b d) (Either c d)
class (Arrow a) => ArrowApply a where
app :: a (a b c, b) c
data ArrowMonad a b = ArrowMonad (a () b)
leftApp :: (ArrowApply a) => a b c -> a (Either b d) (Either c d)
class (Arrow a) => ArrowLoop a where
loop :: a (b, d) (c, d) -> a b c
Arrows
class Arrow a where
The basic arrow class. Any instance must define either arr or pure (which are synonyms), as well as >>> and first. The other combinators have sensible default definitions, which may be overridden for efficiency.
Methods
(&&&) :: a b c -> a b c' -> a b (c, c')
(***) :: a b c -> a b' c' -> a (b, b') (c, c')
second :: a b c -> a (d, b) (d, c)
first :: a b c -> a (b, d) (c, d)

A mirror image of first.

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

(>>>) :: a b c -> a c d -> a b d
Send the first component of the input through the argument arrow, and copy the rest unchanged to the output.
pure :: (b -> c) -> a b c
arr :: (b -> c) -> a b c
Instances
Arrow ->
(Monad m) => Arrow (Kleisli m)
data Kleisli m a b
Kleisli arrows of a monad.
Constructors
Kleisli (a -> m b)
Instances
(Monad m) => Arrow (Kleisli m)
(MonadPlus m) => ArrowZero (Kleisli m)
(MonadPlus m) => ArrowPlus (Kleisli m)
(Monad m) => ArrowChoice (Kleisli m)
(Monad m) => ArrowApply (Kleisli m)
(MonadFix m) => ArrowLoop (Kleisli m)
Derived combinators
returnA :: (Arrow a) => a b b
The identity arrow, which plays the role of return in arrow notation.
(<<<) :: (Arrow a) => a c d -> a b c -> a b d
Right-to-left composition, for a better fit with arrow notation.
Monoid operations
class (Arrow a) => ArrowZero a where
Methods
zeroArrow :: a b c
Instances
(MonadPlus m) => ArrowZero (Kleisli m)
class (ArrowZero a) => ArrowPlus a where
Methods
(<+>) :: a b c -> a b c -> a b c
Instances
(MonadPlus m) => ArrowPlus (Kleisli m)
Conditionals
class (Arrow a) => ArrowChoice a where
Choice, for arrows that support it. This class underlies the if and case constructs in arrow notation. Any instance must define left. The other combinators have sensible default definitions, which may be overridden for efficiency.
Methods
(|||) :: a b d -> a c d -> a (Either b c) d
(+++) :: a b c -> a b' c' -> a (Either b b') (Either c c')
right :: a b c -> a (Either d b) (Either d c)
left :: a b c -> a (Either b d) (Either c d)

A mirror image of left.

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

Instances
ArrowChoice ->
(Monad m) => ArrowChoice (Kleisli m)
Arrow application
class (Arrow a) => ArrowApply a where
Some arrows allow application of arrow inputs to other inputs.
Methods
app :: a (a b c, b) c
Instances
ArrowApply ->
(Monad m) => ArrowApply (Kleisli m)
data ArrowMonad a b
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)
Instances
(ArrowApply a) => Monad (ArrowMonad a)
leftApp :: (ArrowApply a) => a b c -> a (Either b d) (Either c d)
Any instance of ArrowApply can be made into an instance of ArrowChoice by defining left = leftApp.
Feedback
class (Arrow a) => ArrowLoop a where
The loop operator expresses computations in which an output value is fed back as input, even though the computation occurs only once. It underlies the rec value recursion construct in arrow notation.
Methods
loop :: a (b, d) (c, d) -> a b c
Instances
ArrowLoop ->
(MonadFix m) => ArrowLoop (Kleisli m)
Produced by Haddock version 0.3