0d983aba166c5834e599b7e06919caef965637c4
[ghc-base.git] / Control / Arrow.hs
1 -----------------------------------------------------------------------------
2 -- |
3 -- Module      :  Control.Arrow
4 -- Copyright   :  (c) Ross Paterson 2002
5 -- License     :  BSD-style (see the LICENSE file in the distribution)
6 --
7 -- Maintainer  :  libraries@haskell.org
8 -- Stability   :  experimental
9 -- Portability :  portable
10 --
11 -- Basic arrow definitions, based on
12 --      /Generalising Monads to Arrows/, by John Hughes,
13 --      /Science of Computer Programming/ 37, pp67-111, May 2000.
14 -- plus a couple of definitions ('returnA' and 'loop') from
15 --      /A New Notation for Arrows/, by Ross Paterson, in /ICFP 2001/,
16 --      Firenze, Italy, pp229-240.
17 -- See these papers for the equations these combinators are expected to
18 -- satisfy.  These papers and more information on arrows can be found at
19 -- <http://www.haskell.org/arrows/>.
20
21 module Control.Arrow (
22     -- * Arrows
23     Arrow(..), Kleisli(..),
24     -- ** Derived combinators
25     returnA,
26     (^>>), (>>^),
27     (>>>), (<<<), -- reexported
28     -- ** Right-to-left variants
29     (<<^), (^<<),
30     -- * Monoid operations
31     ArrowZero(..), ArrowPlus(..),
32     -- * Conditionals
33     ArrowChoice(..),
34     -- * Arrow application
35     ArrowApply(..), ArrowMonad(..), leftApp,
36     -- * Feedback
37     ArrowLoop(..)
38     ) where
39
40 import Prelude hiding (id,(.))
41
42 import Control.Monad
43 import Control.Monad.Fix
44 import Control.Category
45
46 infixr 5 <+>
47 infixr 3 ***
48 infixr 3 &&&
49 infixr 2 +++
50 infixr 2 |||
51 infixr 1 ^>>, >>^
52 infixr 1 ^<<, <<^
53
54 -- | The basic arrow class.
55 --
56 --   Minimal complete definition: 'arr' and 'first'.
57 --
58 --   The other combinators have sensible default definitions,
59 --   which may be overridden for efficiency.
60
61 class Category a => Arrow a where
62
63     -- | Lift a function to an arrow.
64     arr :: (b -> c) -> a b c
65
66     -- | Send the first component of the input through the argument
67     --   arrow, and copy the rest unchanged to the output.
68     first :: a b c -> a (b,d) (c,d)
69
70     -- | A mirror image of 'first'.
71     --
72     --   The default definition may be overridden with a more efficient
73     --   version if desired.
74     second :: a b c -> a (d,b) (d,c)
75     second f = arr swap >>> first f >>> arr swap
76       where
77         swap :: (x,y) -> (y,x)
78         swap ~(x,y) = (y,x)
79
80     -- | Split the input between the two argument arrows and combine
81     --   their output.  Note that this is in general not a functor.
82     --
83     --   The default definition may be overridden with a more efficient
84     --   version if desired.
85     (***) :: a b c -> a b' c' -> a (b,b') (c,c')
86     f *** g = first f >>> second g
87
88     -- | Fanout: send the input to both argument arrows and combine
89     --   their output.
90     --
91     --   The default definition may be overridden with a more efficient
92     --   version if desired.
93     (&&&) :: a b c -> a b c' -> a b (c,c')
94     f &&& g = arr (\b -> (b,b)) >>> f *** g
95
96 {-# RULES
97 "compose/arr"   forall f g .
98                 (arr f) . (arr g) = arr (f . g)
99 "first/arr"     forall f .
100                 first (arr f) = arr (first f)
101 "second/arr"    forall f .
102                 second (arr f) = arr (second f)
103 "product/arr"   forall f g .
104                 arr f *** arr g = arr (f *** g)
105 "fanout/arr"    forall f g .
106                 arr f &&& arr g = arr (f &&& g)
107 "compose/first" forall f g .
108                 (first f) . (first g) = first (f . g)
109 "compose/second" forall f g .
110                 (second f) . (second g) = second (f . g)
111  #-}
112
113 -- Ordinary functions are arrows.
114
115 instance Arrow (->) where
116     arr f = f
117     first f = f *** id
118     second f = id *** f
119 --  (f *** g) ~(x,y) = (f x, g y)
120 --  sorry, although the above defn is fully H'98, nhc98 can't parse it.
121     (***) f g ~(x,y) = (f x, g y)
122
123 -- | Kleisli arrows of a monad.
124
125 newtype Kleisli m a b = Kleisli { runKleisli :: a -> m b }
126
127 instance Monad m => Category (Kleisli m) where
128     id = Kleisli return
129     (Kleisli f) . (Kleisli g) = Kleisli (\b -> g b >>= f)
130
131 instance Monad m => Arrow (Kleisli m) where
132     arr f = Kleisli (return . f)
133     first (Kleisli f) = Kleisli (\ ~(b,d) -> f b >>= \c -> return (c,d))
134     second (Kleisli f) = Kleisli (\ ~(d,b) -> f b >>= \c -> return (d,c))
135
136 -- | The identity arrow, which plays the role of 'return' in arrow notation.
137
138 returnA :: Arrow a => a b b
139 returnA = arr id
140
141 -- | Precomposition with a pure function.
142 (^>>) :: Arrow a => (b -> c) -> a c d -> a b d
143 f ^>> a = arr f >>> a
144
145 -- | Postcomposition with a pure function.
146 (>>^) :: Arrow a => a b c -> (c -> d) -> a b d
147 a >>^ f = a >>> arr f
148
149 -- | Precomposition with a pure function (right-to-left variant).
150 (<<^) :: Arrow a => a c d -> (b -> c) -> a b d
151 a <<^ f = a <<< arr f
152
153 -- | Postcomposition with a pure function (right-to-left variant).
154 (^<<) :: Arrow a => (c -> d) -> a b c -> a b d
155 f ^<< a = arr f <<< a
156
157 class Arrow a => ArrowZero a where
158     zeroArrow :: a b c
159
160 instance MonadPlus m => ArrowZero (Kleisli m) where
161     zeroArrow = Kleisli (\_ -> mzero)
162
163 class ArrowZero a => ArrowPlus a where
164     (<+>) :: a b c -> a b c -> a b c
165
166 instance MonadPlus m => ArrowPlus (Kleisli m) where
167     Kleisli f <+> Kleisli g = Kleisli (\x -> f x `mplus` g x)
168
169 -- | Choice, for arrows that support it.  This class underlies the
170 --   @if@ and @case@ constructs in arrow notation.
171 --   Any instance must define 'left'.  The other combinators have sensible
172 --   default definitions, which may be overridden for efficiency.
173
174 class Arrow a => ArrowChoice a where
175
176     -- | Feed marked inputs through the argument arrow, passing the
177     --   rest through unchanged to the output.
178     left :: a b c -> a (Either b d) (Either c d)
179
180     -- | A mirror image of 'left'.
181     --
182     --   The default definition may be overridden with a more efficient
183     --   version if desired.
184     right :: a b c -> a (Either d b) (Either d c)
185     right f = arr mirror >>> left f >>> arr mirror
186       where
187         mirror :: Either x y -> Either y x
188         mirror (Left x) = Right x
189         mirror (Right y) = Left y
190
191     -- | Split the input between the two argument arrows, retagging
192     --   and merging their outputs.
193     --   Note that this is in general not a functor.
194     --
195     --   The default definition may be overridden with a more efficient
196     --   version if desired.
197     (+++) :: a b c -> a b' c' -> a (Either b b') (Either c c')
198     f +++ g = left f >>> right g
199
200     -- | Fanin: Split the input between the two argument arrows and
201     --   merge their outputs.
202     --
203     --   The default definition may be overridden with a more efficient
204     --   version if desired.
205     (|||) :: a b d -> a c d -> a (Either b c) d
206     f ||| g = f +++ g >>> arr untag
207       where
208         untag (Left x) = x
209         untag (Right y) = y
210
211 {-# RULES
212 "left/arr"      forall f .
213                 left (arr f) = arr (left f)
214 "right/arr"     forall f .
215                 right (arr f) = arr (right f)
216 "sum/arr"       forall f g .
217                 arr f +++ arr g = arr (f +++ g)
218 "fanin/arr"     forall f g .
219                 arr f ||| arr g = arr (f ||| g)
220 "compose/left"  forall f g .
221                 left f . left g = left (f . g)
222 "compose/right" forall f g .
223                 right f . right g = right (f . g)
224  #-}
225
226 instance ArrowChoice (->) where
227     left f = f +++ id
228     right f = id +++ f
229     f +++ g = (Left . f) ||| (Right . g)
230     (|||) = either
231
232 instance Monad m => ArrowChoice (Kleisli m) where
233     left f = f +++ arr id
234     right f = arr id +++ f
235     f +++ g = (f >>> arr Left) ||| (g >>> arr Right)
236     Kleisli f ||| Kleisli g = Kleisli (either f g)
237
238 -- | Some arrows allow application of arrow inputs to other inputs.
239
240 class Arrow a => ArrowApply a where
241     app :: a (a b c, b) c
242
243 instance ArrowApply (->) where
244     app (f,x) = f x
245
246 instance Monad m => ArrowApply (Kleisli m) where
247     app = Kleisli (\(Kleisli f, x) -> f x)
248
249 -- | The 'ArrowApply' class is equivalent to 'Monad': any monad gives rise
250 --   to a 'Kleisli' arrow, and any instance of 'ArrowApply' defines a monad.
251
252 newtype ArrowApply a => ArrowMonad a b = ArrowMonad (a () b)
253
254 instance ArrowApply a => Monad (ArrowMonad a) where
255     return x = ArrowMonad (arr (\_ -> x))
256     ArrowMonad m >>= f = ArrowMonad $
257         m >>> arr (\x -> let ArrowMonad h = f x in (h, ())) >>> app
258
259 -- | Any instance of 'ArrowApply' can be made into an instance of
260 --   'ArrowChoice' by defining 'left' = 'leftApp'.
261
262 leftApp :: ArrowApply a => a b c -> a (Either b d) (Either c d)
263 leftApp f = arr ((\b -> (arr (\() -> b) >>> f >>> arr Left, ())) |||
264              (\d -> (arr (\() -> d) >>> arr Right, ()))) >>> app
265
266 -- | The 'loop' operator expresses computations in which an output value is
267 --   fed back as input, even though the computation occurs only once.
268 --   It underlies the @rec@ value recursion construct in arrow notation.
269
270 class Arrow a => ArrowLoop a where
271     loop :: a (b,d) (c,d) -> a b c
272
273 instance ArrowLoop (->) where
274     loop f b = let (c,d) = f (b,d) in c
275
276 instance MonadFix m => ArrowLoop (Kleisli m) where
277     loop (Kleisli f) = Kleisli (liftM fst . mfix . f')
278       where f' x y = f (x, snd y)