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