X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=Control%2FArrow.hs;h=2710be6e9c469e3b05da06b1013ad64e4eac610b;hb=567080c906535534628b1ab83a4a4425dcd4bb5e;hp=35cc00de97b22eed44bfbda106ebe27c3eb33cad;hpb=746ef6a7fd71bb1e9ebe3cd107c5f9f79f3b7a68;p=haskell-directory.git diff --git a/Control/Arrow.hs b/Control/Arrow.hs index 35cc00d..2710be6 100644 --- a/Control/Arrow.hs +++ b/Control/Arrow.hs @@ -16,9 +16,27 @@ -- 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 --- . - -module Control.Arrow where +-- . + +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 import Control.Monad import Control.Monad.Fix @@ -28,11 +46,8 @@ 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), @@ -81,6 +96,23 @@ class Arrow a where (&&&) :: a b c -> a b c' -> a b (c,c') f &&& g = arr (\b -> (b,b)) >>> f *** g +{-# RULES +"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 @@ -88,11 +120,13 @@ instance Arrow (->) where 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 => Arrow (Kleisli m) where arr f = Kleisli (return . f) @@ -100,21 +134,30 @@ 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 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 +-- | Postcomposition with a pure function. +(>>^) :: Arrow a => a b c -> (c -> d) -> a b d +a >>^ f = a >>> arr f + +-- | Right-to-left composition, for a better fit with arrow notation. (<<<) :: Arrow a => a c d -> a b c -> a b d f <<< g = g >>> 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 @@ -128,11 +171,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. @@ -170,6 +210,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 @@ -182,9 +237,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 @@ -214,12 +266,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