comments for Applicative and Traversable
[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         -- * Instances
29         WrappedMonad(..), Const(..), ZipList(..),
30         -- * Utility functions
31         (<$>), (<$), (*>), (<*), (<**>),
32         liftA, liftA2, liftA3
33         ) where
34
35 #ifdef __HADDOCK__
36 import Prelude
37 #endif
38
39 import Control.Monad (liftM, ap)
40 import Control.Monad.Instances ()
41 import Data.Monoid (Monoid(..))
42
43 infixl 4 <$>, <$
44 infixl 4 <*>, <*, *>, <**>
45
46 -- | A functor with application.
47 --
48 -- Instances should satisfy the following laws:
49 --
50 -- [/identity/]
51 --      @'pure' 'id' '<*>' v = v@
52 --
53 -- [/composition/]
54 --      @'pure' (.) '<*>' u '<*>' v '<*>' w = u '<*>' (v '<*>' w)@
55 --
56 -- [/homomorphism/]
57 --      @'pure' f '<*>' 'pure' x = 'pure' (f x)@
58 --
59 -- [/interchange/]
60 --      @u '<*>' 'pure' y = 'pure' ('$' y) '<*>' u@
61 --
62 -- The 'Functor' instance should satisfy
63 --
64 -- @
65 --      'fmap' f x = 'pure' f '<*>' x
66 -- @
67 --
68 -- If @f@ is also a 'Monad', define @'pure' = 'return'@ and @('<*>') = 'ap'@.
69
70 class Functor f => Applicative f where
71         -- | Lift a value.
72         pure :: a -> f a
73
74         -- | Sequential application.
75         (<*>) :: f (a -> b) -> f a -> f b
76
77 -- instances for Prelude types
78
79 instance Applicative Maybe where
80         pure = return
81         (<*>) = ap
82
83 instance Applicative [] where
84         pure = return
85         (<*>) = ap
86
87 instance Applicative IO where
88         pure = return
89         (<*>) = ap
90
91 instance Applicative ((->) a) where
92         pure = const
93         (<*>) f g x = f x (g x)
94
95 instance Monoid a => Applicative ((,) a) where
96         pure x = (mempty, x)
97         (u, f) <*> (v, x) = (u `mappend` v, f x)
98
99 -- new instances
100
101 newtype WrappedMonad m a = WrapMonad { unwrapMonad :: m a }
102
103 instance Monad m => Functor (WrappedMonad m) where
104         fmap f (WrapMonad v) = WrapMonad (liftM f v)
105
106 instance Monad m => Applicative (WrappedMonad m) where
107         pure = WrapMonad . return
108         WrapMonad f <*> WrapMonad v = WrapMonad (f `ap` v)
109
110 newtype Const a b = Const { getConst :: a }
111
112 instance Functor (Const m) where
113         fmap _ (Const v) = Const v
114
115 instance Monoid m => Applicative (Const m) where
116         pure _ = Const mempty
117         Const f <*> Const v = Const (f `mappend` v)
118
119 -- | Lists, but with an 'Applicative' functor based on zipping, so that
120 --
121 -- @f '<$>' 'ZipList' xs1 '<*>' ... '<*>' 'ZipList' xsn = 'ZipList' (zipWithn f xs1 ... xsn)@
122 --
123 newtype ZipList a = ZipList { getZipList :: [a] }
124
125 instance Functor ZipList where
126         fmap f (ZipList xs) = ZipList (map f xs)
127
128 instance Applicative ZipList where
129         pure x = ZipList (repeat x)
130         ZipList fs <*> ZipList xs = ZipList (zipWith id fs xs)
131
132 -- extra functions
133
134 -- | A synonym for 'fmap'.
135 (<$>) :: Functor f => (a -> b) -> f a -> f b
136 f <$> a = fmap f a
137
138 -- | Replace the value.
139 (<$) :: Functor f => a -> f b -> f a
140 (<$) = (<$>) . const
141  
142 -- | Sequence actions, discarding the value of the first argument.
143 (*>) :: Applicative f => f a -> f b -> f b
144 (*>) = liftA2 (const id)
145  
146 -- | Sequence actions, discarding the value of the second argument.
147 (<*) :: Applicative f => f a -> f b -> f a
148 (<*) = liftA2 const
149  
150 -- | A variant of '<*>' with the arguments reversed.
151 (<**>) :: Applicative f => f a -> f (a -> b) -> f b
152 (<**>) = liftA2 (flip ($))
153
154 -- | Lift a function to actions.
155 -- This function may be used as a value for `fmap` in a `Functor` instance.
156 liftA :: Applicative f => (a -> b) -> f a -> f b
157 liftA f a = pure f <*> a
158
159 -- | Lift a binary function to actions.
160 liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c
161 liftA2 f a b = f <$> a <*> b
162
163 -- | Lift a ternary function to actions.
164 liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
165 liftA3 f a b c = f <$> a <*> b <*> c