Use explicit language extensions & remove extension fields from base.cabal
[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: it provides pure expressions and sequencing, but no binding.
15 -- (Technically, a strong lax monoidal functor.)  For more details, see
16 -- /Applicative Programming with Effects/,
17 -- by Conor McBride and Ross Paterson, online at
18 -- <http://www.soi.city.ac.uk/~ross/papers/Applicative.html>.
19 --
20 -- This interface was introduced for parsers by Niklas R&#xF6;jemo, because
21 -- it admits more sharing than the monadic interface.  The names here are
22 -- mostly based on recent parsing work by Doaitse Swierstra.
23 --
24 -- This class is also useful with instances of the
25 -- 'Data.Traversable.Traversable' class.
26
27 module Control.Applicative (
28     -- * Applicative functors
29     Applicative(..),
30     -- * Alternatives
31     Alternative(..),
32     -- * Instances
33     Const(..), WrappedMonad(..), WrappedArrow(..), ZipList(..),
34     -- * Utility functions
35     (<$>), (<$), (<**>),
36     liftA, liftA2, liftA3,
37     optional,
38     ) where
39
40 import Prelude hiding (id,(.))
41
42 import Control.Category
43 import Control.Arrow (Arrow(arr, (&&&)), ArrowZero(zeroArrow), ArrowPlus((<+>)))
44 import Control.Monad (liftM, ap, MonadPlus(..))
45 import Control.Monad.Instances ()
46 #ifndef __NHC__
47 import Control.Monad.ST (ST)
48 import qualified Control.Monad.ST.Lazy as Lazy (ST)
49 #endif
50 import Data.Functor ((<$>), (<$))
51 import Data.Monoid (Monoid(..))
52
53 #ifdef __GLASGOW_HASKELL__
54 import GHC.Conc (STM, retry, orElse)
55 #endif
56
57 infixl 3 <|>
58 infixl 4 <*>, <*, *>, <**>
59
60 -- | A functor with application.
61 --
62 -- Instances should satisfy the following laws:
63 --
64 -- [/identity/]
65 --      @'pure' 'id' '<*>' v = v@
66 --
67 -- [/composition/]
68 --      @'pure' (.) '<*>' u '<*>' v '<*>' w = u '<*>' (v '<*>' w)@
69 --
70 -- [/homomorphism/]
71 --      @'pure' f '<*>' 'pure' x = 'pure' (f x)@
72 --
73 -- [/interchange/]
74 --      @u '<*>' 'pure' y = 'pure' ('$' y) '<*>' u@
75 --
76 -- [/ignore left value/]
77 --      @u '*>' v = 'pure' ('const' 'id') '<*>' u '<*>' v@
78 --
79 -- [/ignore right value/]
80 --      @u '<*' v = 'pure' 'const' '<*>' u '<*>' v@
81 --
82 -- The 'Functor' instance should satisfy
83 --
84 -- @
85 --      'fmap' f x = 'pure' f '<*>' x
86 -- @
87 --
88 -- If @f@ is also a 'Monad', define @'pure' = 'return'@ and @('<*>') = 'ap'@.
89 --
90 -- Minimal complete definition: 'pure' and '<*>'.
91
92 class Functor f => Applicative f where
93     -- | Lift a value.
94     pure :: a -> f a
95
96     -- | Sequential application.
97     (<*>) :: f (a -> b) -> f a -> f b
98
99     -- | Sequence actions, discarding the value of the first argument.
100     (*>) :: f a -> f b -> f b
101     (*>) = liftA2 (const id)
102
103     -- | Sequence actions, discarding the value of the second argument.
104     (<*) :: f a -> f b -> f a
105     (<*) = liftA2 const
106
107 -- | A monoid on applicative functors.
108 --
109 -- Minimal complete definition: 'empty' and '<|>'.
110 --
111 -- 'some' and 'many' should be the least solutions of the equations:
112 --
113 -- * @some v = (:) '<$>' v '<*>' many v@
114 --
115 -- * @many v = some v '<|>' 'pure' []@
116 class Applicative f => Alternative f where
117     -- | The identity of '<|>'
118     empty :: f a
119     -- | An associative binary operation
120     (<|>) :: f a -> f a -> f a
121
122     -- | One or more.
123     some :: f a -> f [a]
124     some v = some_v
125       where
126         many_v = some_v <|> pure []
127         some_v = (:) <$> v <*> many_v
128
129     -- | Zero or more.
130     many :: f a -> f [a]
131     many v = many_v
132       where
133         many_v = some_v <|> pure []
134         some_v = (:) <$> v <*> many_v
135
136 -- instances for Prelude types
137
138 instance Applicative Maybe where
139     pure = return
140     (<*>) = ap
141
142 instance Alternative Maybe where
143     empty = Nothing
144     Nothing <|> p = p
145     Just x <|> _ = Just x
146
147 instance Applicative [] where
148     pure = return
149     (<*>) = ap
150
151 instance Alternative [] where
152     empty = []
153     (<|>) = (++)
154
155 instance Applicative IO where
156     pure = return
157     (<*>) = ap
158
159 #ifndef __NHC__
160 instance Applicative (ST s) where
161     pure = return
162     (<*>) = ap
163
164 instance Applicative (Lazy.ST s) where
165     pure = return
166     (<*>) = ap
167 #endif
168
169 #ifdef __GLASGOW_HASKELL__
170 instance Applicative STM where
171     pure = return
172     (<*>) = ap
173
174 instance Alternative STM where
175     empty = retry
176     (<|>) = orElse
177 #endif
178
179 instance Applicative ((->) a) where
180     pure = const
181     (<*>) f g x = f x (g x)
182
183 instance Monoid a => Applicative ((,) a) where
184     pure x = (mempty, x)
185     (u, f) <*> (v, x) = (u `mappend` v, f x)
186
187 instance Applicative (Either e) where
188     pure          = Right
189     Left  e <*> _ = Left e
190     Right f <*> r = fmap f r
191
192 -- new instances
193
194 newtype Const a b = Const { getConst :: a }
195
196 instance Functor (Const m) where
197     fmap _ (Const v) = Const v
198
199 instance Monoid m => Applicative (Const m) where
200     pure _ = Const mempty
201     Const f <*> Const v = Const (f `mappend` v)
202
203 newtype WrappedMonad m a = WrapMonad { unwrapMonad :: m a }
204
205 instance Monad m => Functor (WrappedMonad m) where
206     fmap f (WrapMonad v) = WrapMonad (liftM f v)
207
208 instance Monad m => Applicative (WrappedMonad m) where
209     pure = WrapMonad . return
210     WrapMonad f <*> WrapMonad v = WrapMonad (f `ap` v)
211
212 instance MonadPlus m => Alternative (WrappedMonad m) where
213     empty = WrapMonad mzero
214     WrapMonad u <|> WrapMonad v = WrapMonad (u `mplus` v)
215
216 newtype WrappedArrow a b c = WrapArrow { unwrapArrow :: a b c }
217
218 instance Arrow a => Functor (WrappedArrow a b) where
219     fmap f (WrapArrow a) = WrapArrow (a >>> arr f)
220
221 instance Arrow a => Applicative (WrappedArrow a b) where
222     pure x = WrapArrow (arr (const x))
223     WrapArrow f <*> WrapArrow v = WrapArrow (f &&& v >>> arr (uncurry id))
224
225 instance (ArrowZero a, ArrowPlus a) => Alternative (WrappedArrow a b) where
226     empty = WrapArrow zeroArrow
227     WrapArrow u <|> WrapArrow v = WrapArrow (u <+> v)
228
229 -- | Lists, but with an 'Applicative' functor based on zipping, so that
230 --
231 -- @f '<$>' 'ZipList' xs1 '<*>' ... '<*>' 'ZipList' xsn = 'ZipList' (zipWithn f xs1 ... xsn)@
232 --
233 newtype ZipList a = ZipList { getZipList :: [a] }
234
235 instance Functor ZipList where
236     fmap f (ZipList xs) = ZipList (map f xs)
237
238 instance Applicative ZipList where
239     pure x = ZipList (repeat x)
240     ZipList fs <*> ZipList xs = ZipList (zipWith id fs xs)
241
242 -- extra functions
243
244 -- | A variant of '<*>' with the arguments reversed.
245 (<**>) :: Applicative f => f a -> f (a -> b) -> f b
246 (<**>) = liftA2 (flip ($))
247
248 -- | Lift a function to actions.
249 -- This function may be used as a value for `fmap` in a `Functor` instance.
250 liftA :: Applicative f => (a -> b) -> f a -> f b
251 liftA f a = pure f <*> a
252
253 -- | Lift a binary function to actions.
254 liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c
255 liftA2 f a b = f <$> a <*> b
256
257 -- | Lift a ternary function to actions.
258 liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
259 liftA3 f a b c = f <$> a <*> b <*> c
260
261 -- | One or none.
262 optional :: Alternative f => f a -> f (Maybe a)
263 optional v = Just <$> v <|> pure Nothing