34783e02cfe0a19edf89c82ab9ab3c532acb515e
[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 -- $Id: Arrow.hs,v 1.2 2002/04/24 17:57:55 ross Exp $
12 --
13 -- Basic arrow definitions, based on
14 --      /Generalising Monads to Arrows/, by John Hughes,
15 --      /Science of Computer Programming/ 37, pp67-111, May 2000.
16 -- plus a couple of definitions ('returnA' and 'loop') from
17 --      /A New Notation for Arrows/, by Ross Paterson, in /ICFP 2001/,
18 --      Firenze, Italy, pp229-240.
19 -- See these papers for the equations these combinators are expected to
20 -- satisfy.  These papers and more information on arrows can be found at
21 -- <http://www.soi.city.ac.uk/~ross/arrows/>.
22
23 module Control.Arrow where
24
25 import Control.Monad
26 import Control.Monad.Fix
27
28 infixr 5 <+>
29 infixr 3 ***
30 infixr 3 &&&
31 infixr 2 +++
32 infixr 2 |||
33 infixr 1 >>>
34 infixr 1 <<<
35
36 -----------------------------------------------------------------------------
37 -- * Arrows
38
39 -- | The basic arrow class.
40 --   Any instance must define either 'arr' or 'pure' (which are synonyms),
41 --   as well as '>>>' and 'first'.  The other combinators have sensible
42 --   default definitions, which may be overridden for efficiency.
43
44 class Arrow a where
45
46         -- | Lift a function to an arrow: you must define either this
47         --   or 'pure'.
48         arr :: (b -> c) -> a b c
49         arr = pure
50
51         -- | A synonym for 'arr': you must define one or other of them.
52         pure :: (b -> c) -> a b c
53         pure = arr
54
55         -- | Left-to-right composition of arrows.
56         (>>>) :: a b c -> a c d -> a b d
57
58         -- | Send the first component of the input through the argument
59         --   arrow, and copy the rest unchanged to the output.
60         first :: a b c -> a (b,d) (c,d)
61
62         -- | A mirror image of 'first'.
63         --
64         --   The default definition may be overridden with a more efficient
65         --   version if desired.
66         second :: a b c -> a (d,b) (d,c)
67         second f = arr swap >>> first f >>> arr swap
68                         where   swap ~(x,y) = (y,x)
69
70         -- | Split the input between the two argument arrows and combine
71         --   their output.  Note that this is in general not a functor.
72         --
73         --   The default definition may be overridden with a more efficient
74         --   version if desired.
75         (***) :: a b c -> a b' c' -> a (b,b') (c,c')
76         f *** g = first f >>> second g
77
78         -- | Fanout: send the input to both argument arrows and combine
79         --   their output.
80         --
81         --   The default definition may be overridden with a more efficient
82         --   version if desired.
83         (&&&) :: a b c -> a b c' -> a b (c,c')
84         f &&& g = arr (\b -> (b,b)) >>> f *** g
85
86 -- Ordinary functions are arrows.
87
88 instance Arrow (->) where
89         arr f = f
90         f >>> g = g . f
91         first f = f *** id
92         second f = id *** f
93         (f *** g) ~(x,y) = (f x, g y)
94
95 -- | Kleisli arrows of a monad.
96
97 newtype Kleisli m a b = Kleisli (a -> m b)
98
99 instance Monad m => Arrow (Kleisli m) where
100         arr f = Kleisli (return . f)
101         Kleisli f >>> Kleisli g = Kleisli (\b -> f b >>= g)
102         first (Kleisli f) = Kleisli (\ ~(b,d) -> f b >>= \c -> return (c,d))
103         second (Kleisli f) = Kleisli (\ ~(d,b) -> f b >>= \c -> return (d,c))
104
105 -----------------------------------------------------------------------------
106 -- ** Derived combinators
107
108 -- | The identity arrow, which plays the role of 'return' in arrow notation.
109
110 returnA :: Arrow a => a b b
111 returnA = arr id
112
113 -- | Right-to-left composition, for a better fit with arrow notation.
114
115 (<<<) :: Arrow a => a c d -> a b c -> a b d
116 f <<< g = g >>> f
117
118 -----------------------------------------------------------------------------
119 -- * Monoid operations
120
121 class Arrow a => ArrowZero a where
122         zeroArrow :: a b c
123
124 instance MonadPlus m => ArrowZero (Kleisli m) where
125         zeroArrow = Kleisli (\x -> mzero)
126
127 class ArrowZero a => ArrowPlus a where
128         (<+>) :: a b c -> a b c -> a b c
129
130 instance MonadPlus m => ArrowPlus (Kleisli m) where
131         Kleisli f <+> Kleisli g = Kleisli (\x -> f x `mplus` g x)
132
133 -----------------------------------------------------------------------------
134 -- * Conditionals
135
136 -- | Choice, for arrows that support it.  This class underlies the
137 --   [if] and [case] constructs in arrow notation.
138 --   Any instance must define 'left'.  The other combinators have sensible
139 --   default definitions, which may be overridden for efficiency.
140
141 class Arrow a => ArrowChoice a where
142
143         -- | Feed marked inputs through the argument arrow, passing the
144         --   rest through unchanged to the output.
145         left :: a b c -> a (Either b d) (Either c d)
146
147         -- | A mirror image of 'left'.
148         --
149         --   The default definition may be overridden with a more efficient
150         --   version if desired.
151         right :: a b c -> a (Either d b) (Either d c)
152         right f = arr mirror >>> left f >>> arr mirror
153                         where   mirror (Left x) = Right x
154                                 mirror (Right y) = Left y
155
156         -- | Split the input between the two argument arrows, retagging
157         --   and merging their outputs.
158         --   Note that this is in general not a functor.
159         --
160         --   The default definition may be overridden with a more efficient
161         --   version if desired.
162         (+++) :: a b c -> a b' c' -> a (Either b b') (Either c c')
163         f +++ g = left f >>> right g
164
165         -- | Fanin: Split the input between the two argument arrows and
166         --   merge their outputs.
167         --
168         --   The default definition may be overridden with a more efficient
169         --   version if desired.
170         (|||) :: a b d -> a c d -> a (Either b c) d
171         f ||| g = f +++ g >>> arr untag
172                         where   untag (Left x) = x
173                                 untag (Right y) = y
174
175 instance ArrowChoice (->) where
176         left f = f +++ id
177         right f = id +++ f
178         f +++ g = (Left . f) ||| (Right . g)
179         (|||) = either
180
181 instance Monad m => ArrowChoice (Kleisli m) where
182         left f = f +++ arr id
183         right f = arr id +++ f
184         f +++ g = (f >>> arr Left) ||| (g >>> arr Right)
185         Kleisli f ||| Kleisli g = Kleisli (either f g)
186
187 -----------------------------------------------------------------------------
188 -- * Arrow application
189
190 -- | Some arrows allow application of arrow inputs to other inputs.
191
192 class Arrow a => ArrowApply a where
193         app :: a (a b c, b) c
194
195 instance ArrowApply (->) where
196         app (f,x) = f x
197
198 instance Monad m => ArrowApply (Kleisli m) where
199         app = Kleisli (\(Kleisli f, x) -> f x)
200
201 -- | The 'ArrowApply' class is equivalent to 'Monad': any monad gives rise
202 --   to a 'Kleisli' arrow, and any instance of 'ArrowApply' defines a monad.
203
204 newtype ArrowApply a => ArrowMonad a b = ArrowMonad (a () b)
205
206 instance ArrowApply a => Monad (ArrowMonad a) where
207         return x = ArrowMonad (arr (\z -> x))
208         ArrowMonad m >>= f = ArrowMonad (m >>>
209                         arr (\x -> let ArrowMonad h = f x in (h, ())) >>>
210                         app)
211
212 -- | Any instance of 'ArrowApply' can be made into an instance of
213 --   'ArrowChoice' by defining 'left' = 'leftApp'.
214
215 leftApp :: ArrowApply a => a b c -> a (Either b d) (Either c d)
216 leftApp f = arr ((\b -> (arr (\() -> b) >>> f >>> arr Left, ())) |||
217                  (\d -> (arr (\() -> d) >>> arr Right, ()))) >>> app
218
219 -----------------------------------------------------------------------------
220 -- * Feedback
221
222 -- | The 'loop' operator expresses computations in which an output value is
223 --   fed back as input, even though the computation occurs only once.
224 --   It underlies the [rec] value recursion construct in arrow notation.
225
226 class Arrow a => ArrowLoop a where
227         loop :: a (b,d) (c,d) -> a b c
228
229 instance ArrowLoop (->) where
230         loop f b = let (c,d) = f (b,d) in c
231
232 instance MonadFix m => ArrowLoop (Kleisli m) where
233         loop (Kleisli f) = Kleisli (liftM fst . mfix . f')
234                 where   f' x y = f (x, snd y)