[project @ 2002-02-26 18:19:17 by ross]
[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  :  ross@soi.city.ac.uk
8 -- Stability   :  experimental
9 -- Portability :  portable
10 --
11 -- $Id: Arrow.hs,v 1.1 2002/02/26 18:19:17 ross Exp $
12 --
13 -- Basic arrow definitions, based on
14 --
15 --      "Generalising Monads to Arrows", by John Hughes, Science of
16 --      Computer Programming 37, pp67-111, May 2000.
17 --
18 -- plus a couple of definitions (returnA and loop) from
19 --
20 --      "A New Notation for Arrows", by Ross Paterson, in ICFP 2001,
21 --      Firenze, Italy, pp229-240.
22 --
23 -- See these papers for the equations these combinators are expected to
24 -- satisfy.  These papers and more information on arrows can be found at
25 --
26 --      http://www.soi.city.ac.uk/~ross/arrows/
27 --
28 -----------------------------------------------------------------------------
29
30 module Control.Arrow where
31
32 import Prelude
33
34 import Control.Monad
35 import Control.Monad.Fix
36
37 infixr 5 <+>
38 infixr 3 ***
39 infixr 3 &&&
40 infixr 2 +++
41 infixr 2 |||
42 infixr 1 >>>
43 infixr 1 <<<
44
45 -----------------------------------------------------------------------------
46 -- Arrow classes
47
48 class Arrow a where
49         arr :: (b -> c) -> a b c
50         (>>>) :: a b c -> a c d -> a b d
51         first :: a b c -> a (b,d) (c,d)
52
53         -- The following combinators are placed in the class so that they
54         -- can be overridden with more efficient versions if required.
55         -- Any replacements should satisfy these equations.
56
57         second :: a b c -> a (d,b) (d,c)
58         second f = arr swap >>> first f >>> arr swap
59                         where   swap ~(x,y) = (y,x)
60
61         (***) :: a b c -> a b' c' -> a (b,b') (c,c')
62         f *** g = first f >>> second g
63
64         (&&&) :: a b c -> a b c' -> a b (c,c')
65         f &&& g = arr (\b -> (b,b)) >>> f *** g
66
67         -- Some people prefer the name pure to arr, so both are allowed,
68         -- but you must define one of them:
69
70         pure :: (b -> c) -> a b c
71         pure = arr
72         arr = pure
73
74 -----------------------------------------------------------------------------
75 -- Derived combinators
76
77 -- The counterpart of return in arrow notation:
78
79 returnA :: Arrow a => a b b
80 returnA = arr id
81
82 -- Mirror image of >>>, for a better fit with arrow notation:
83
84 (<<<) :: Arrow a => a c d -> a b c -> a b d
85 f <<< g = g >>> f
86
87 -----------------------------------------------------------------------------
88 -- Monoid operations
89
90 class Arrow a => ArrowZero a where
91         zeroArrow :: a b c
92
93 class ArrowZero a => ArrowPlus a where
94         (<+>) :: a b c -> a b c -> a b c
95
96 -----------------------------------------------------------------------------
97 -- Conditionals
98
99 class Arrow a => ArrowChoice a where
100         left :: a b c -> a (Either b d) (Either c d)
101
102         -- The following combinators are placed in the class so that they
103         -- can be overridden with more efficient versions if required.
104         -- Any replacements should satisfy these equations.
105
106         right :: a b c -> a (Either d b) (Either d c)
107         right f = arr mirror >>> left f >>> arr mirror
108                         where   mirror (Left x) = Right x
109                                 mirror (Right y) = Left y
110
111         (+++) :: a b c -> a b' c' -> a (Either b b') (Either c c')
112         f +++ g = left f >>> right g
113
114         (|||) :: a b d -> a c d -> a (Either b c) d
115         f ||| g = f +++ g >>> arr untag
116                         where   untag (Left x) = x
117                                 untag (Right y) = y
118
119 -----------------------------------------------------------------------------
120 -- Arrow application
121
122 class Arrow a => ArrowApply a where
123         app :: a (a b c, b) c
124
125 -- Any instance of ArrowApply can be made into an instance if ArrowChoice
126 -- by defining left = leftApp, where
127
128 leftApp :: ArrowApply a => a b c -> a (Either b d) (Either c d)
129 leftApp f = arr ((\b -> (arr (\() -> b) >>> f >>> arr Left, ())) |||
130                  (\d -> (arr (\() -> d) >>> arr Right, ()))) >>> app
131
132 -- The ArrowApply class is equivalent to Monad: any monad gives rise to
133 -- a Kliesli arrow (see below), and any instance of ArrowApply defines
134 -- a monad:
135
136 newtype ArrowApply a => ArrowMonad a b = ArrowMonad (a () b)
137
138 instance ArrowApply a => Monad (ArrowMonad a) where
139         return x = ArrowMonad (arr (\z -> x))
140         ArrowMonad m >>= f = ArrowMonad (m >>>
141                         arr (\x -> let ArrowMonad h = f x in (h, ())) >>>
142                         app)
143
144 -----------------------------------------------------------------------------
145 -- Feedback
146
147 -- The following operator expresses computations in which a value is
148 -- recursively defined through the computation, even though the computation
149 -- occurs only once:
150
151 class Arrow a => ArrowLoop a where
152         loop :: a (b,d) (c,d) -> a b c
153
154 -----------------------------------------------------------------------------
155 -- Arrow instances
156
157 -- Ordinary functions are arrows.
158
159 instance Arrow (->) where
160         arr f = f
161         f >>> g = g . f
162         first f = f *** id
163         second f = id *** f
164         (f *** g) ~(x,y) = (f x, g y)
165
166 instance ArrowChoice (->) where
167         left f = f +++ id
168         right f = id +++ f
169         f +++ g = (Left . f) ||| (Right . g)
170         (|||) = either
171
172 instance ArrowApply (->) where
173         app (f,x) = f x
174
175 instance ArrowLoop (->) where
176         loop f b = let (c,d) = f (b,d) in c
177
178 -----------------------------------------------------------------------------
179 -- Kleisli arrows of a monad
180
181 newtype Kleisli m a b = Kleisli (a -> m b)
182
183 instance Monad m => Arrow (Kleisli m) where
184         arr f = Kleisli (return . f)
185         Kleisli f >>> Kleisli g = Kleisli (\b -> f b >>= g)
186         first (Kleisli f) = Kleisli (\ ~(b,d) -> f b >>= \c -> return (c,d))
187         second (Kleisli f) = Kleisli (\ ~(d,b) -> f b >>= \c -> return (d,c))
188
189 instance MonadPlus m => ArrowZero (Kleisli m) where
190         zeroArrow = Kleisli (\x -> mzero)
191
192 instance MonadPlus m => ArrowPlus (Kleisli m) where
193         Kleisli f <+> Kleisli g = Kleisli (\x -> f x `mplus` g x)
194
195 instance Monad m => ArrowChoice (Kleisli m) where
196         left f = f +++ arr id
197         right f = arr id +++ f
198         f +++ g = (f >>> arr Left) ||| (g >>> arr Right)
199         Kleisli f ||| Kleisli g = Kleisli (either f g)
200
201 instance Monad m => ArrowApply (Kleisli m) where
202         app = Kleisli (\(Kleisli f, x) -> f x)
203
204 instance MonadFix m => ArrowLoop (Kleisli m) where
205         loop (Kleisli f) = Kleisli (liftM fst . mfix . f')
206                 where   f' x y = f (x, snd y)