[project @ 2005-11-29 14:31:59 by ross]
[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 -- <http://www.soi.city.ac.uk/~ross/papers/Applicative.html>.
15 --
16 -- This interface was introduced for parsers by Niklas R&#xF6;jemo, because
17 -- it admits more sharing than the monadic interface.  The names here are
18 -- mostly based on recent parsing work by Doaitse Swierstra.
19 --
20 -- This class is also useful with instances of the
21 -- 'Data.Traversable.Traversable' class.
22
23 module Control.Applicative (
24         -- * Applicative functors
25         Applicative(..),
26         -- * Instances
27         WrappedMonad(..), Const(..), ZipList(..),
28         -- * Utility functions
29         (<$), (*>), (<*), (<**>),
30         liftA, liftA2, liftA3
31         ) where
32
33 #ifdef __HADDOCK__
34 import Prelude
35 #endif
36
37 import Control.Monad (liftM, ap)
38 import Data.Monoid (Monoid(..))
39
40 infixl 4 <$>, <$
41 infixl 4 <*>, <*, *>, <**>
42
43 -- | A functor with application.
44 --
45 -- Instances should satisfy the following laws:
46 --
47 -- [/identity/]
48 --      @'pure' 'id' '<*>' v = v@
49 --
50 -- [/composition/]
51 --      @'pure' (.) '<*>' u '<*>' v '<*>' w = u '<*>' (v '<*>' w)@
52 --
53 -- [/homomorphism/]
54 --      @'pure' f '<*>' 'pure' x = 'pure' (f x)@
55 --
56 -- [/interchange/]
57 --      @u '<*>' 'pure' y = 'pure' ('$' y) '<*>' u@
58 --
59 -- [/pure application/]
60 --      @f '<$>' v = 'pure' f '<*>' v@
61 --
62 -- Minimal complete definition: 'pure' and '<*>'.
63 --
64 -- If @f@ is also a 'Functor', define @('<$>') = 'fmap'@.
65 -- If it is also a 'Monad', define @'pure' = 'return'@ and @('<*>') = 'ap'@.
66
67 class Applicative f where
68         -- | Lift a value.
69         pure :: a -> f a
70
71         -- | Sequential application.
72         (<*>) :: f (a -> b) -> f a -> f b
73
74         -- | Map a function over an action.
75         (<$>) :: (a -> b) -> f a -> f b
76         f <$> v = pure f <*> v
77
78 -- instances for Prelude types
79
80 instance Applicative Maybe where
81         pure = return
82         (<*>) = ap
83
84 instance Applicative [] where
85         pure = return
86         (<*>) = ap
87
88 instance Applicative IO where
89         pure = return
90         (<*>) = ap
91
92 instance Applicative ((->) a) where
93         pure = const
94         (<*>) f g x = f x (g x)
95
96 -- new instances
97
98 newtype WrappedMonad m a = WrapMonad { unwrapMonad :: m a }
99
100 instance Monad m => Applicative (WrappedMonad m) where
101         pure = WrapMonad . return
102         WrapMonad f <*> WrapMonad v = WrapMonad (f `ap` v)
103         f <$> WrapMonad v = WrapMonad (liftM f v)
104
105 newtype Const a b = Const { getConst :: a }
106
107 instance Monoid m => Applicative (Const m) where
108         pure _ = Const mempty
109         Const f <*> Const v = Const (f `mappend` v)
110         _ <$> Const v = Const v
111
112 -- | Lists, but with an 'Applicative' functor based on zipping, so that
113 --
114 -- @f '<$>' 'ZipList' xs1 '<*>' ... '<*>' 'ZipList' xsn = 'ZipList' (zipWithn f xs1 ... xsn)@
115 --
116 newtype ZipList a = ZipList { getZipList :: [a] }
117
118 instance Applicative ZipList where
119         pure x = ZipList (repeat x)
120         ZipList fs <*> ZipList xs = ZipList (zipWith id fs xs)
121         f <$> ZipList xs = ZipList (map f xs)
122
123 -- extra functions
124
125 -- | Replace the value.
126 (<$) :: Applicative f => a -> f b -> f a
127 (<$) = (<$>) . const
128  
129 -- | Sequence actions, discarding the value of the first argument.
130 (*>) :: Applicative f => f a -> f b -> f b
131 (*>) = liftA2 (const id)
132  
133 -- | Sequence actions, discarding the value of the second argument.
134 (<*) :: Applicative f => f a -> f b -> f a
135 (<*) = liftA2 const
136  
137 -- | A variant of '<*>' with the arguments reversed.
138 (<**>) :: Applicative f => f a -> f (a -> b) -> f b
139 (<**>) = liftA2 (flip ($))
140
141 -- | A synonym for '<$>'.
142 liftA :: Applicative f => (a -> b) -> f a -> f b
143 liftA f a = f <$> a
144
145 -- | Lift a binary function to actions.
146 liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c
147 liftA2 f a b = f <$> a <*> b
148
149 -- | Lift a ternary function to actions.
150 liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
151 liftA3 f a b c = f <$> a <*> b <*> c