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