summaryrefslogtreecommitdiff
path: root/libraries/base/Control/Arrow.hs
diff options
context:
space:
mode:
authorross <unknown>2002-06-05 11:30:38 +0000
committerross <unknown>2002-06-05 11:30:38 +0000
commita734568b72fefb946df47a4fe21b3babee1664f1 (patch)
tree60194737905b220daef66e219b522f177e09c75d /libraries/base/Control/Arrow.hs
parent2bf1f14ee184b021c52564d273ff094d5d3a2087 (diff)
downloadhaskell-a734568b72fefb946df47a4fe21b3babee1664f1.tar.gz
[project @ 2002-06-05 11:30:38 by ross]
documentation adjustments.
Diffstat (limited to 'libraries/base/Control/Arrow.hs')
-rw-r--r--libraries/base/Control/Arrow.hs41
1 files changed, 18 insertions, 23 deletions
diff --git a/libraries/base/Control/Arrow.hs b/libraries/base/Control/Arrow.hs
index 04f31a6df5..fd1552a057 100644
--- a/libraries/base/Control/Arrow.hs
+++ b/libraries/base/Control/Arrow.hs
@@ -16,9 +16,22 @@
-- 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.soi.city.ac.uk/~ross/arrows/>.
-
-module Control.Arrow where
+-- <http://www.haskell.org/arrows/>.
+
+module Control.Arrow (
+ -- * Arrows
+ Arrow(..), Kleisli(..),
+ -- ** Derived combinators
+ returnA, (<<<),
+ -- * Monoid operations
+ ArrowZero(..), ArrowPlus(..),
+ -- * Conditionals
+ ArrowChoice(..),
+ -- * Arrow application
+ ArrowApply(..), ArrowMonad(..), leftApp,
+ -- * Feedback
+ ArrowLoop(..)
+ ) where
import Prelude
@@ -33,9 +46,6 @@ infixr 2 |||
infixr 1 >>>
infixr 1 <<<
------------------------------------------------------------------------------
--- * Arrows
-
-- | 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
@@ -102,9 +112,6 @@ instance Monad m => Arrow (Kleisli m) where
first (Kleisli f) = Kleisli (\ ~(b,d) -> f b >>= \c -> return (c,d))
second (Kleisli f) = Kleisli (\ ~(d,b) -> f b >>= \c -> return (d,c))
------------------------------------------------------------------------------
--- ** Derived combinators
-
-- | The identity arrow, which plays the role of 'return' in arrow notation.
returnA :: Arrow a => a b b
@@ -115,9 +122,6 @@ returnA = arr id
(<<<) :: Arrow a => a c d -> a b c -> a b d
f <<< g = g >>> f
------------------------------------------------------------------------------
--- * Monoid operations
-
class Arrow a => ArrowZero a where
zeroArrow :: a b c
@@ -130,11 +134,8 @@ class ArrowZero a => ArrowPlus a where
instance MonadPlus m => ArrowPlus (Kleisli m) where
Kleisli f <+> Kleisli g = Kleisli (\x -> f x `mplus` g x)
------------------------------------------------------------------------------
--- * Conditionals
-
-- | Choice, for arrows that support it. This class underlies the
--- [if] and [case] constructs in arrow notation.
+-- @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.
@@ -184,9 +185,6 @@ instance Monad m => ArrowChoice (Kleisli m) where
f +++ g = (f >>> arr Left) ||| (g >>> arr Right)
Kleisli f ||| Kleisli g = Kleisli (either f g)
------------------------------------------------------------------------------
--- * Arrow application
-
-- | Some arrows allow application of arrow inputs to other inputs.
class Arrow a => ArrowApply a where
@@ -216,12 +214,9 @@ leftApp :: ArrowApply a => a b c -> a (Either b d) (Either c d)
leftApp f = arr ((\b -> (arr (\() -> b) >>> f >>> arr Left, ())) |||
(\d -> (arr (\() -> d) >>> arr Right, ()))) >>> app
------------------------------------------------------------------------------
--- * Feedback
-
-- | 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.
+-- It underlies the @rec@ value recursion construct in arrow notation.
class Arrow a => ArrowLoop a where
loop :: a (b,d) (c,d) -> a b c