[project @ 2002-06-05 11:30:38 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 -- 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                 -- * Monoid operations
27                 ArrowZero(..), ArrowPlus(..),
28                 -- * Conditionals
29                 ArrowChoice(..),
30                 -- * Arrow application
31                 ArrowApply(..), ArrowMonad(..), leftApp,
32                 -- * Feedback
33                 ArrowLoop(..)
34         ) where
35
36 import Prelude
37
38 import Control.Monad
39 import Control.Monad.Fix
40
41 infixr 5 <+>
42 infixr 3 ***
43 infixr 3 &&&
44 infixr 2 +++
45 infixr 2 |||
46 infixr 1 >>>
47 infixr 1 <<<
48
49 -- | The basic arrow class.
50 --   Any instance must define either 'arr' or 'pure' (which are synonyms),
51 --   as well as '>>>' and 'first'.  The other combinators have sensible
52 --   default definitions, which may be overridden for efficiency.
53
54 class Arrow a where
55
56         -- | Lift a function to an arrow: you must define either this
57         --   or 'pure'.
58         arr :: (b -> c) -> a b c
59         arr = pure
60
61         -- | A synonym for 'arr': you must define one or other of them.
62         pure :: (b -> c) -> a b c
63         pure = arr
64
65         -- | Left-to-right composition of arrows.
66         (>>>) :: a b c -> a c d -> a b d
67
68         -- | Send the first component of the input through the argument
69         --   arrow, and copy the rest unchanged to the output.
70         first :: a b c -> a (b,d) (c,d)
71
72         -- | A mirror image of 'first'.
73         --
74         --   The default definition may be overridden with a more efficient
75         --   version if desired.
76         second :: a b c -> a (d,b) (d,c)
77         second f = arr swap >>> first f >>> arr swap
78                         where   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 -- Ordinary functions are arrows.
97
98 instance Arrow (->) where
99         arr f = f
100         f >>> g = g . f
101         first f = f *** id
102         second f = id *** f
103         (f *** g) ~(x,y) = (f x, g y)
104
105 -- | Kleisli arrows of a monad.
106
107 newtype Kleisli m a b = Kleisli (a -> m b)
108
109 instance Monad m => Arrow (Kleisli m) where
110         arr f = Kleisli (return . f)
111         Kleisli f >>> Kleisli g = Kleisli (\b -> f b >>= g)
112         first (Kleisli f) = Kleisli (\ ~(b,d) -> f b >>= \c -> return (c,d))
113         second (Kleisli f) = Kleisli (\ ~(d,b) -> f b >>= \c -> return (d,c))
114
115 -- | The identity arrow, which plays the role of 'return' in arrow notation.
116
117 returnA :: Arrow a => a b b
118 returnA = arr id
119
120 -- | Right-to-left composition, for a better fit with arrow notation.
121
122 (<<<) :: Arrow a => a c d -> a b c -> a b d
123 f <<< g = g >>> f
124
125 class Arrow a => ArrowZero a where
126         zeroArrow :: a b c
127
128 instance MonadPlus m => ArrowZero (Kleisli m) where
129         zeroArrow = Kleisli (\x -> mzero)
130
131 class ArrowZero a => ArrowPlus a where
132         (<+>) :: a b c -> a b c -> a b c
133
134 instance MonadPlus m => ArrowPlus (Kleisli m) where
135         Kleisli f <+> Kleisli g = Kleisli (\x -> f x `mplus` g x)
136
137 -- | Choice, for arrows that support it.  This class underlies the
138 --   @if@ and @case@ constructs in arrow notation.
139 --   Any instance must define 'left'.  The other combinators have sensible
140 --   default definitions, which may be overridden for efficiency.
141
142 class Arrow a => ArrowChoice a where
143
144         -- | Feed marked inputs through the argument arrow, passing the
145         --   rest through unchanged to the output.
146         left :: a b c -> a (Either b d) (Either c d)
147
148         -- | A mirror image of 'left'.
149         --
150         --   The default definition may be overridden with a more efficient
151         --   version if desired.
152         right :: a b c -> a (Either d b) (Either d c)
153         right f = arr mirror >>> left f >>> arr mirror
154                         where   mirror (Left x) = Right x
155                                 mirror (Right y) = Left y
156
157         -- | Split the input between the two argument arrows, retagging
158         --   and merging their outputs.
159         --   Note that this is in general not a functor.
160         --
161         --   The default definition may be overridden with a more efficient
162         --   version if desired.
163         (+++) :: a b c -> a b' c' -> a (Either b b') (Either c c')
164         f +++ g = left f >>> right g
165
166         -- | Fanin: Split the input between the two argument arrows and
167         --   merge their outputs.
168         --
169         --   The default definition may be overridden with a more efficient
170         --   version if desired.
171         (|||) :: a b d -> a c d -> a (Either b c) d
172         f ||| g = f +++ g >>> arr untag
173                         where   untag (Left x) = x
174                                 untag (Right y) = y
175
176 instance ArrowChoice (->) where
177         left f = f +++ id
178         right f = id +++ f
179         f +++ g = (Left . f) ||| (Right . g)
180         (|||) = either
181
182 instance Monad m => ArrowChoice (Kleisli m) where
183         left f = f +++ arr id
184         right f = arr id +++ f
185         f +++ g = (f >>> arr Left) ||| (g >>> arr Right)
186         Kleisli f ||| Kleisli g = Kleisli (either f g)
187
188 -- | Some arrows allow application of arrow inputs to other inputs.
189
190 class Arrow a => ArrowApply a where
191         app :: a (a b c, b) c
192
193 instance ArrowApply (->) where
194         app (f,x) = f x
195
196 instance Monad m => ArrowApply (Kleisli m) where
197         app = Kleisli (\(Kleisli f, x) -> f x)
198
199 -- | The 'ArrowApply' class is equivalent to 'Monad': any monad gives rise
200 --   to a 'Kleisli' arrow, and any instance of 'ArrowApply' defines a monad.
201
202 newtype ArrowApply a => ArrowMonad a b = ArrowMonad (a () b)
203
204 instance ArrowApply a => Monad (ArrowMonad a) where
205         return x = ArrowMonad (arr (\z -> x))
206         ArrowMonad m >>= f = ArrowMonad (m >>>
207                         arr (\x -> let ArrowMonad h = f x in (h, ())) >>>
208                         app)
209
210 -- | Any instance of 'ArrowApply' can be made into an instance of
211 --   'ArrowChoice' by defining 'left' = 'leftApp'.
212
213 leftApp :: ArrowApply a => a b c -> a (Either b d) (Either c d)
214 leftApp f = arr ((\b -> (arr (\() -> b) >>> f >>> arr Left, ())) |||
215                  (\d -> (arr (\() -> d) >>> arr Right, ()))) >>> app
216
217 -- | The 'loop' operator expresses computations in which an output value is
218 --   fed back as input, even though the computation occurs only once.
219 --   It underlies the @rec@ value recursion construct in arrow notation.
220
221 class Arrow a => ArrowLoop a where
222         loop :: a (b,d) (c,d) -> a b c
223
224 instance ArrowLoop (->) where
225         loop f b = let (c,d) = f (b,d) in c
226
227 instance MonadFix m => ArrowLoop (Kleisli m) where
228         loop (Kleisli f) = Kleisli (liftM fst . mfix . f')
229                 where   f' x y = f (x, snd y)