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