add GHC.HetMet.{hetmet_kappa,hetmet_kappa_app}
[ghc-base.git] / Control / Applicative.hs
1 {-# LANGUAGE CPP #-}
2
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  Control.Applicative
6 -- Copyright   :  Conor McBride and Ross Paterson 2005
7 -- License     :  BSD-style (see the LICENSE file in the distribution)
8 --
9 -- Maintainer  :  libraries@haskell.org
10 -- Stability   :  experimental
11 -- Portability :  portable
12 --
13 -- This module describes a structure intermediate between a functor and
14 -- a monad (technically, a strong lax monoidal functor).  Compared with
15 -- monads, this interface lacks the full power of the binding operation
16 -- '>>=', but
17 --
18 -- * it has more instances.
19 --
20 -- * it is sufficient for many uses, e.g. context-free parsing, or the
21 --   'Data.Traversable.Traversable' class.
22 --
23 -- * instances can perform analysis of computations before they are
24 --   executed, and thus produce shared optimizations.
25 --
26 -- This interface was introduced for parsers by Niklas Röjemo, because
27 -- it admits more sharing than the monadic interface.  The names here are
28 -- mostly based on parsing work by Doaitse Swierstra.
29 --
30 -- For more details, see /Applicative Programming with Effects/,
31 -- by Conor McBride and Ross Paterson, online at
32 -- <http://www.soi.city.ac.uk/~ross/papers/Applicative.html>.
33
34 module Control.Applicative (
35     -- * Applicative functors
36     Applicative(..),
37     -- * Alternatives
38     Alternative(..),
39     -- * Instances
40     Const(..), WrappedMonad(..), WrappedArrow(..), ZipList(..),
41     -- * Utility functions
42     (<$>), (<$), (<**>),
43     liftA, liftA2, liftA3,
44     optional,
45     ) where
46
47 import Prelude hiding (id,(.))
48
49 import Control.Category
50 import Control.Arrow (Arrow(arr, (&&&)), ArrowZero(zeroArrow), ArrowPlus((<+>)))
51 import Control.Monad (liftM, ap, MonadPlus(..))
52 import Control.Monad.Instances ()
53 #ifndef __NHC__
54 import Control.Monad.ST (ST)
55 import qualified Control.Monad.ST.Lazy as Lazy (ST)
56 #endif
57 import Data.Functor ((<$>), (<$))
58 import Data.Monoid (Monoid(..))
59
60 #ifdef __GLASGOW_HASKELL__
61 import GHC.Conc (STM, retry, orElse)
62 #endif
63
64 infixl 3 <|>
65 infixl 4 <*>, <*, *>, <**>
66
67 -- | A functor with application, providing operations to
68 --
69 -- * embed pure expressions ('pure'), and
70 --
71 -- * sequence computations and combine their results ('<*>').
72 --
73 -- A minimal complete definition must include implementations of these
74 -- functions satisfying the following laws:
75 --
76 -- [/identity/]
77 --      @'pure' 'id' '<*>' v = v@
78 --
79 -- [/composition/]
80 --      @'pure' (.) '<*>' u '<*>' v '<*>' w = u '<*>' (v '<*>' w)@
81 --
82 -- [/homomorphism/]
83 --      @'pure' f '<*>' 'pure' x = 'pure' (f x)@
84 --
85 -- [/interchange/]
86 --      @u '<*>' 'pure' y = 'pure' ('$' y) '<*>' u@
87 --
88 -- The other methods have the following default definitions, which may
89 -- be overridden with equivalent specialized implementations:
90 --
91 -- @
92 --      u '*>' v = 'pure' ('const' 'id') '<*>' u '<*>' v
93 --      u '<*' v = 'pure' 'const' '<*>' u '<*>' v
94 -- @
95 --
96 -- As a consequence of these laws, the 'Functor' instance for @f@ will satisfy
97 --
98 -- @
99 --      'fmap' f x = 'pure' f '<*>' x
100 -- @
101 --
102 -- If @f@ is also a 'Monad', it should satisfy @'pure' = 'return'@ and
103 -- @('<*>') = 'ap'@ (which implies that 'pure' and '<*>' satisfy the
104 -- applicative functor laws).
105
106 class Functor f => Applicative f where
107     -- | Lift a value.
108     pure :: a -> f a
109
110     -- | Sequential application.
111     (<*>) :: f (a -> b) -> f a -> f b
112
113     -- | Sequence actions, discarding the value of the first argument.
114     (*>) :: f a -> f b -> f b
115     (*>) = liftA2 (const id)
116
117     -- | Sequence actions, discarding the value of the second argument.
118     (<*) :: f a -> f b -> f a
119     (<*) = liftA2 const
120
121 -- | A monoid on applicative functors.
122 --
123 -- Minimal complete definition: 'empty' and '<|>'.
124 --
125 -- If defined, 'some' and 'many' should be the least solutions
126 -- of the equations:
127 --
128 -- * @some v = (:) '<$>' v '<*>' many v@
129 --
130 -- * @many v = some v '<|>' 'pure' []@
131 class Applicative f => Alternative f where
132     -- | The identity of '<|>'
133     empty :: f a
134     -- | An associative binary operation
135     (<|>) :: f a -> f a -> f a
136
137     -- | One or more.
138     some :: f a -> f [a]
139     some v = some_v
140       where
141         many_v = some_v <|> pure []
142         some_v = (:) <$> v <*> many_v
143
144     -- | Zero or more.
145     many :: f a -> f [a]
146     many v = many_v
147       where
148         many_v = some_v <|> pure []
149         some_v = (:) <$> v <*> many_v
150
151 -- instances for Prelude types
152
153 instance Applicative Maybe where
154     pure = return
155     (<*>) = ap
156
157 instance Alternative Maybe where
158     empty = Nothing
159     Nothing <|> p = p
160     Just x <|> _ = Just x
161
162 instance Applicative [] where
163     pure = return
164     (<*>) = ap
165
166 instance Alternative [] where
167     empty = []
168     (<|>) = (++)
169
170 instance Applicative IO where
171     pure = return
172     (<*>) = ap
173
174 #ifndef __NHC__
175 instance Applicative (ST s) where
176     pure = return
177     (<*>) = ap
178
179 instance Applicative (Lazy.ST s) where
180     pure = return
181     (<*>) = ap
182 #endif
183
184 #ifdef __GLASGOW_HASKELL__
185 instance Applicative STM where
186     pure = return
187     (<*>) = ap
188
189 instance Alternative STM where
190     empty = retry
191     (<|>) = orElse
192 #endif
193
194 instance Applicative ((->) a) where
195     pure = const
196     (<*>) f g x = f x (g x)
197
198 instance Monoid a => Applicative ((,) a) where
199     pure x = (mempty, x)
200     (u, f) <*> (v, x) = (u `mappend` v, f x)
201
202 instance Applicative (Either e) where
203     pure          = Right
204     Left  e <*> _ = Left e
205     Right f <*> r = fmap f r
206
207 -- new instances
208
209 newtype Const a b = Const { getConst :: a }
210
211 instance Functor (Const m) where
212     fmap _ (Const v) = Const v
213
214 instance Monoid m => Applicative (Const m) where
215     pure _ = Const mempty
216     Const f <*> Const v = Const (f `mappend` v)
217
218 newtype WrappedMonad m a = WrapMonad { unwrapMonad :: m a }
219
220 instance Monad m => Functor (WrappedMonad m) where
221     fmap f (WrapMonad v) = WrapMonad (liftM f v)
222
223 instance Monad m => Applicative (WrappedMonad m) where
224     pure = WrapMonad . return
225     WrapMonad f <*> WrapMonad v = WrapMonad (f `ap` v)
226
227 instance MonadPlus m => Alternative (WrappedMonad m) where
228     empty = WrapMonad mzero
229     WrapMonad u <|> WrapMonad v = WrapMonad (u `mplus` v)
230
231 newtype WrappedArrow a b c = WrapArrow { unwrapArrow :: a b c }
232
233 instance Arrow a => Functor (WrappedArrow a b) where
234     fmap f (WrapArrow a) = WrapArrow (a >>> arr f)
235
236 instance Arrow a => Applicative (WrappedArrow a b) where
237     pure x = WrapArrow (arr (const x))
238     WrapArrow f <*> WrapArrow v = WrapArrow (f &&& v >>> arr (uncurry id))
239
240 instance (ArrowZero a, ArrowPlus a) => Alternative (WrappedArrow a b) where
241     empty = WrapArrow zeroArrow
242     WrapArrow u <|> WrapArrow v = WrapArrow (u <+> v)
243
244 -- | Lists, but with an 'Applicative' functor based on zipping, so that
245 --
246 -- @f '<$>' 'ZipList' xs1 '<*>' ... '<*>' 'ZipList' xsn = 'ZipList' (zipWithn f xs1 ... xsn)@
247 --
248 newtype ZipList a = ZipList { getZipList :: [a] }
249
250 instance Functor ZipList where
251     fmap f (ZipList xs) = ZipList (map f xs)
252
253 instance Applicative ZipList where
254     pure x = ZipList (repeat x)
255     ZipList fs <*> ZipList xs = ZipList (zipWith id fs xs)
256
257 -- extra functions
258
259 -- | A variant of '<*>' with the arguments reversed.
260 (<**>) :: Applicative f => f a -> f (a -> b) -> f b
261 (<**>) = liftA2 (flip ($))
262
263 -- | Lift a function to actions.
264 -- This function may be used as a value for `fmap` in a `Functor` instance.
265 liftA :: Applicative f => (a -> b) -> f a -> f b
266 liftA f a = pure f <*> a
267
268 -- | Lift a binary function to actions.
269 liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c
270 liftA2 f a b = f <$> a <*> b
271
272 -- | Lift a ternary function to actions.
273 liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
274 liftA3 f a b c = f <$> a <*> b <*> c
275
276 -- | One or none.
277 optional :: Alternative f => f a -> f (Maybe a)
278 optional v = Just <$> v <|> pure Nothing