fix nhc98 build: need a qualified Prelude import
[ghc-base.git] / Control / Arrow.hs
index 04f31a6..66c7745 100644 (file)
 --     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
-
-import Prelude
+-- <http://www.haskell.org/arrows/>.
+
+module Control.Arrow (
+               -- * Arrows
+               Arrow(..), Kleisli(..),
+               -- ** Derived combinators
+               returnA,
+               (^>>), (>>^),
+               -- ** Right-to-left variants
+               (<<^), (^<<),
+               -- * Monoid operations
+               ArrowZero(..), ArrowPlus(..),
+               -- * Conditionals
+               ArrowChoice(..),
+               -- * Arrow application
+               ArrowApply(..), ArrowMonad(..), leftApp,
+               -- * Feedback
+               ArrowLoop(..)
+       ) where
+
+import Prelude hiding (id,(.))
+import qualified Prelude
 
 import Control.Monad
 import Control.Monad.Fix
+import Control.Category
 
 infixr 5 <+>
 infixr 3 ***
 infixr 3 &&&
 infixr 2 +++
 infixr 2 |||
-infixr 1 >>>
-infixr 1 <<<
-
------------------------------------------------------------------------------
--- * Arrows
+infixr 1 ^>>, >>^
+infixr 1 ^<<, <<^
 
 -- | 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
+--   as well as 'first'.  The other combinators have sensible
 --   default definitions, which may be overridden for efficiency.
 
-class Arrow a where
+class Category a => Arrow a where
 
        -- | Lift a function to an arrow: you must define either this
        --   or 'pure'.
@@ -52,9 +67,6 @@ class Arrow a where
        pure :: (b -> c) -> a b c
        pure = arr
 
-       -- | Left-to-right composition of arrows.
-       (>>>) :: 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.
        first :: a b c -> a (b,d) (c,d)
@@ -83,40 +95,68 @@ class Arrow a where
        (&&&) :: a b c -> a b c' -> a b (c,c')
        f &&& g = arr (\b -> (b,b)) >>> f *** g
 
+{-# RULES
+"identity"
+               arr id = id
+"compose/arr"  forall f g .
+               (arr f) . (arr g) = arr (f . g)
+"first/arr"    forall f .
+               first (arr f) = arr (first f)
+"second/arr"   forall f .
+               second (arr f) = arr (second f)
+"product/arr"  forall f g .
+               arr f *** arr g = arr (f *** g)
+"fanout/arr"   forall f g .
+               arr f &&& arr g = arr (f &&& g)
+"compose/first"        forall f g .
+               (first f) . (first g) = first (f . g)
+"compose/second" forall f g .
+               (second f) . (second g) = second (f . g)
+ #-}
+
 -- Ordinary functions are arrows.
 
 instance Arrow (->) where
        arr f = f
-       f >>> g = g . f
        first f = f *** id
        second f = id *** f
-       (f *** g) ~(x,y) = (f x, g y)
+--     (f *** g) ~(x,y) = (f x, g y)
+--     sorry, although the above defn is fully H'98, nhc98 can't parse it.
+       (***) f g ~(x,y) = (f x, g y)
 
 -- | Kleisli arrows of a monad.
 
-newtype Kleisli m a b = Kleisli (a -> m b)
+newtype Kleisli m a b = Kleisli { runKleisli :: a -> m b }
+
+instance Monad m => Category (Kleisli m) where
+       id = Kleisli return
+       (Kleisli f) . (Kleisli g) = Kleisli (\b -> g b >>= f)
 
 instance Monad m => Arrow (Kleisli m) where
        arr f = Kleisli (return . f)
-       Kleisli f >>> Kleisli g = Kleisli (\b -> f b >>= g)
        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
 returnA = arr id
 
--- | Right-to-left composition, for a better fit with arrow notation.
+-- | Precomposition with a pure function.
+(^>>) :: Arrow a => (b -> c) -> a c d -> a b d
+f ^>> a = arr f >>> a
 
-(<<<) :: Arrow a => a c d -> a b c -> a b d
-f <<< g = g >>> f
+-- | Postcomposition with a pure function.
+(>>^) :: Arrow a => a b c -> (c -> d) -> a b d
+a >>^ f = a >>> arr f
 
------------------------------------------------------------------------------
--- * Monoid operations
+-- | Precomposition with a pure function (right-to-left variant).
+(<<^) :: Arrow a => a c d -> (b -> c) -> a b d
+a <<^ f = a <<< arr f
+
+-- | Postcomposition with a pure function (right-to-left variant).
+(^<<) :: Arrow a => (c -> d) -> a b c -> a b d
+f ^<< a = arr f <<< a
 
 class Arrow a => ArrowZero a where
        zeroArrow :: a b c
@@ -130,11 +170,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.
 
@@ -172,6 +209,21 @@ class Arrow a => ArrowChoice a where
                        where   untag (Left x) = x
                                untag (Right y) = y
 
+{-# RULES
+"left/arr"     forall f .
+               left (arr f) = arr (left f)
+"right/arr"    forall f .
+               right (arr f) = arr (right f)
+"sum/arr"      forall f g .
+               arr f +++ arr g = arr (f +++ g)
+"fanin/arr"    forall f g .
+               arr f ||| arr g = arr (f ||| g)
+"compose/left" forall f g .
+               left f >>> left g = left (f >>> g)
+"compose/right"        forall f g .
+               right f >>> right g = right (f >>> g)
+ #-}
+
 instance ArrowChoice (->) where
        left f = f +++ id
        right f = id +++ f
@@ -184,9 +236,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 +265,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