Remove Control.Parallel*, now in package parallel
[haskell-directory.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  :  ross@soi.city.ac.uk
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                 -- ** Right-to-left variants
28                 (<<<), (<<^), (^<<),
29                 -- * Monoid operations
30                 ArrowZero(..), ArrowPlus(..),
31                 -- * Conditionals
32                 ArrowChoice(..),
33                 -- * Arrow application
34                 ArrowApply(..), ArrowMonad(..), leftApp,
35                 -- * Feedback
36                 ArrowLoop(..)
37         ) where
38
39 import Prelude
40
41 import Control.Monad
42 import Control.Monad.Fix
43
44 infixr 5 <+>
45 infixr 3 ***
46 infixr 3 &&&
47 infixr 2 +++
48 infixr 2 |||
49 infixr 1 >>>, ^>>, >>^
50 infixr 1 <<<, ^<<, <<^
51
52 -- | The basic arrow class.
53 --   Any instance must define either 'arr' or 'pure' (which are synonyms),
54 --   as well as '>>>' and 'first'.  The other combinators have sensible
55 --   default definitions, which may be overridden for efficiency.
56
57 class Arrow a where
58
59         -- | Lift a function to an arrow: you must define either this
60         --   or 'pure'.
61         arr :: (b -> c) -> a b c
62         arr = pure
63
64         -- | A synonym for 'arr': you must define one or other of them.
65         pure :: (b -> c) -> a b c
66         pure = arr
67
68         -- | Left-to-right composition of arrows.
69         (>>>) :: a b c -> a c d -> a b d
70
71         -- | Send the first component of the input through the argument
72         --   arrow, and copy the rest unchanged to the output.
73         first :: a b c -> a (b,d) (c,d)
74
75         -- | A mirror image of 'first'.
76         --
77         --   The default definition may be overridden with a more efficient
78         --   version if desired.
79         second :: a b c -> a (d,b) (d,c)
80         second f = arr swap >>> first f >>> arr swap
81                         where   swap ~(x,y) = (y,x)
82
83         -- | Split the input between the two argument arrows and combine
84         --   their output.  Note that this is in general not a functor.
85         --
86         --   The default definition may be overridden with a more efficient
87         --   version if desired.
88         (***) :: a b c -> a b' c' -> a (b,b') (c,c')
89         f *** g = first f >>> second g
90
91         -- | Fanout: send the input to both argument arrows and combine
92         --   their output.
93         --
94         --   The default definition may be overridden with a more efficient
95         --   version if desired.
96         (&&&) :: a b c -> a b c' -> a b (c,c')
97         f &&& g = arr (\b -> (b,b)) >>> f *** g
98
99 {-# RULES
100 "compose/arr"   forall f g .
101                 arr f >>> arr g = arr (f >>> g)
102 "first/arr"     forall f .
103                 first (arr f) = arr (first f)
104 "second/arr"    forall f .
105                 second (arr f) = arr (second f)
106 "product/arr"   forall f g .
107                 arr f *** arr g = arr (f *** g)
108 "fanout/arr"    forall f g .
109                 arr f &&& arr g = arr (f &&& g)
110 "compose/first" forall f g .
111                 first f >>> first g = first (f >>> g)
112 "compose/second" forall f g .
113                 second f >>> second g = second (f >>> g)
114  #-}
115
116 -- Ordinary functions are arrows.
117
118 instance Arrow (->) where
119         arr f = f
120         f >>> g = g . f
121         first f = f *** id
122         second f = id *** f
123 --      (f *** g) ~(x,y) = (f x, g y)
124 --      sorry, although the above defn is fully H'98, nhc98 can't parse it.
125         (***) f g ~(x,y) = (f x, g y)
126
127 -- | Kleisli arrows of a monad.
128
129 newtype Kleisli m a b = Kleisli { runKleisli :: a -> m b }
130
131 instance Monad m => Arrow (Kleisli m) where
132         arr f = Kleisli (return . f)
133         Kleisli f >>> Kleisli g = Kleisli (\b -> f b >>= g)
134         first (Kleisli f) = Kleisli (\ ~(b,d) -> f b >>= \c -> return (c,d))
135         second (Kleisli f) = Kleisli (\ ~(d,b) -> f b >>= \c -> return (d,c))
136
137 -- | The identity arrow, which plays the role of 'return' in arrow notation.
138
139 returnA :: Arrow a => a b b
140 returnA = arr id
141
142 -- | Precomposition with a pure function.
143 (^>>) :: Arrow a => (b -> c) -> a c d -> a b d
144 f ^>> a = arr f >>> a
145
146 -- | Postcomposition with a pure function.
147 (>>^) :: Arrow a => a b c -> (c -> d) -> a b d
148 a >>^ f = a >>> arr f
149
150 -- | Right-to-left composition, for a better fit with arrow notation.
151 (<<<) :: Arrow a => a c d -> a b c -> a b d
152 f <<< g = g >>> f
153
154 -- | Precomposition with a pure function (right-to-left variant).
155 (<<^) :: Arrow a => a c d -> (b -> c) -> a b d
156 a <<^ f = a <<< arr f
157
158 -- | Postcomposition with a pure function (right-to-left variant).
159 (^<<) :: Arrow a => (c -> d) -> a b c -> a b d
160 f ^<< a = arr f <<< a
161
162 class Arrow a => ArrowZero a where
163         zeroArrow :: a b c
164
165 instance MonadPlus m => ArrowZero (Kleisli m) where
166         zeroArrow = Kleisli (\x -> mzero)
167
168 class ArrowZero a => ArrowPlus a where
169         (<+>) :: a b c -> a b c -> a b c
170
171 instance MonadPlus m => ArrowPlus (Kleisli m) where
172         Kleisli f <+> Kleisli g = Kleisli (\x -> f x `mplus` g x)
173
174 -- | Choice, for arrows that support it.  This class underlies the
175 --   @if@ and @case@ constructs in arrow notation.
176 --   Any instance must define 'left'.  The other combinators have sensible
177 --   default definitions, which may be overridden for efficiency.
178
179 class Arrow a => ArrowChoice a where
180
181         -- | Feed marked inputs through the argument arrow, passing the
182         --   rest through unchanged to the output.
183         left :: a b c -> a (Either b d) (Either c d)
184
185         -- | A mirror image of 'left'.
186         --
187         --   The default definition may be overridden with a more efficient
188         --   version if desired.
189         right :: a b c -> a (Either d b) (Either d c)
190         right f = arr mirror >>> left f >>> arr mirror
191                         where   mirror (Left x) = Right x
192                                 mirror (Right y) = Left y
193
194         -- | Split the input between the two argument arrows, retagging
195         --   and merging their outputs.
196         --   Note that this is in general not a functor.
197         --
198         --   The default definition may be overridden with a more efficient
199         --   version if desired.
200         (+++) :: a b c -> a b' c' -> a (Either b b') (Either c c')
201         f +++ g = left f >>> right g
202
203         -- | Fanin: Split the input between the two argument arrows and
204         --   merge their outputs.
205         --
206         --   The default definition may be overridden with a more efficient
207         --   version if desired.
208         (|||) :: a b d -> a c d -> a (Either b c) d
209         f ||| g = f +++ g >>> arr untag
210                         where   untag (Left x) = x
211                                 untag (Right y) = y
212
213 {-# RULES
214 "left/arr"      forall f .
215                 left (arr f) = arr (left f)
216 "right/arr"     forall f .
217                 right (arr f) = arr (right f)
218 "sum/arr"       forall f g .
219                 arr f +++ arr g = arr (f +++ g)
220 "fanin/arr"     forall f g .
221                 arr f ||| arr g = arr (f ||| g)
222 "compose/left"  forall f g .
223                 left f >>> left g = left (f >>> g)
224 "compose/right" forall f g .
225                 right f >>> right g = right (f >>> g)
226  #-}
227
228 instance ArrowChoice (->) where
229         left f = f +++ id
230         right f = id +++ f
231         f +++ g = (Left . f) ||| (Right . g)
232         (|||) = either
233
234 instance Monad m => ArrowChoice (Kleisli m) where
235         left f = f +++ arr id
236         right f = arr id +++ f
237         f +++ g = (f >>> arr Left) ||| (g >>> arr Right)
238         Kleisli f ||| Kleisli g = Kleisli (either f g)
239
240 -- | Some arrows allow application of arrow inputs to other inputs.
241
242 class Arrow a => ArrowApply a where
243         app :: a (a b c, b) c
244
245 instance ArrowApply (->) where
246         app (f,x) = f x
247
248 instance Monad m => ArrowApply (Kleisli m) where
249         app = Kleisli (\(Kleisli f, x) -> f x)
250
251 -- | The 'ArrowApply' class is equivalent to 'Monad': any monad gives rise
252 --   to a 'Kleisli' arrow, and any instance of 'ArrowApply' defines a monad.
253
254 newtype ArrowApply a => ArrowMonad a b = ArrowMonad (a () b)
255
256 instance ArrowApply a => Monad (ArrowMonad a) where
257         return x = ArrowMonad (arr (\z -> x))
258         ArrowMonad m >>= f = ArrowMonad (m >>>
259                         arr (\x -> let ArrowMonad h = f x in (h, ())) >>>
260                         app)
261
262 -- | Any instance of 'ArrowApply' can be made into an instance of
263 --   'ArrowChoice' by defining 'left' = 'leftApp'.
264
265 leftApp :: ArrowApply a => a b c -> a (Either b d) (Either c d)
266 leftApp f = arr ((\b -> (arr (\() -> b) >>> f >>> arr Left, ())) |||
267                  (\d -> (arr (\() -> d) >>> arr Right, ()))) >>> app
268
269 -- | The 'loop' operator expresses computations in which an output value is
270 --   fed back as input, even though the computation occurs only once.
271 --   It underlies the @rec@ value recursion construct in arrow notation.
272
273 class Arrow a => ArrowLoop a where
274         loop :: a (b,d) (c,d) -> a b c
275
276 instance ArrowLoop (->) where
277         loop f b = let (c,d) = f (b,d) in c
278
279 instance MonadFix m => ArrowLoop (Kleisli m) where
280         loop (Kleisli f) = Kleisli (liftM fst . mfix . f')
281                 where   f' x y = f (x, snd y)