a0e3b20eff6b979a84b73f4cd78d1333f4f04f52
[ghc-base.git] / Data / Monoid.hs
1 -----------------------------------------------------------------------------
2 -- |
3 -- Module      :  Data.Monoid
4 -- Copyright   :  (c) Andy Gill 2001,
5 --                (c) Oregon Graduate Institute of Science and Technology, 2001
6 -- License     :  BSD-style (see the file libraries/base/LICENSE)
7 --
8 -- Maintainer  :  libraries@haskell.org
9 -- Stability   :  experimental
10 -- Portability :  portable
11 --
12 -- A class for monoids (types with an associative binary operation that
13 -- has an identity) with various general-purpose instances.
14 -----------------------------------------------------------------------------
15
16 module Data.Monoid (
17         -- * Monoid typeclass
18         Monoid(..),
19         Dual(..),
20         Endo(..),
21         -- * Bool wrappers
22         All(..),
23         Any(..),
24         -- * Num wrappers
25         Sum(..),
26         Product(..),
27         -- * Maybe wrappers
28         -- $MaybeExamples
29         First(..),
30         Last(..)
31   ) where
32
33 import Prelude
34
35 {-
36 -- just for testing
37 import Data.Maybe
38 import Test.QuickCheck
39 -- -}
40
41 -- ---------------------------------------------------------------------------
42 -- | The class of monoids (types with an associative binary operation that
43 -- has an identity).  The method names refer to the monoid of lists,
44 -- but there are many other instances.
45 --
46 -- Minimal complete definition: 'mempty' and 'mappend'.
47 --
48 -- Some types can be viewed as a monoid in more than one way,
49 -- e.g. both addition and multiplication on numbers.
50 -- In such cases we often define @newtype@s and make those instances
51 -- of 'Monoid', e.g. 'Sum' and 'Product'.
52
53 class Monoid a where
54         mempty  :: a
55         -- ^ Identity of 'mappend'
56         mappend :: a -> a -> a
57         -- ^ An associative operation
58         mconcat :: [a] -> a
59
60         -- ^ Fold a list using the monoid.
61         -- For most types, the default definition for 'mconcat' will be
62         -- used, but the function is included in the class definition so
63         -- that an optimized version can be provided for specific types.
64
65         mconcat = foldr mappend mempty
66
67 -- Monoid instances.
68
69 instance Monoid [a] where
70         mempty  = []
71         mappend = (++)
72
73 instance Monoid b => Monoid (a -> b) where
74         mempty _ = mempty
75         mappend f g x = f x `mappend` g x
76
77 instance Monoid () where
78         -- Should it be strict?
79         mempty        = ()
80         _ `mappend` _ = ()
81         mconcat _     = ()
82
83 instance (Monoid a, Monoid b) => Monoid (a,b) where
84         mempty = (mempty, mempty)
85         (a1,b1) `mappend` (a2,b2) =
86                 (a1 `mappend` a2, b1 `mappend` b2)
87
88 instance (Monoid a, Monoid b, Monoid c) => Monoid (a,b,c) where
89         mempty = (mempty, mempty, mempty)
90         (a1,b1,c1) `mappend` (a2,b2,c2) =
91                 (a1 `mappend` a2, b1 `mappend` b2, c1 `mappend` c2)
92
93 instance (Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a,b,c,d) where
94         mempty = (mempty, mempty, mempty, mempty)
95         (a1,b1,c1,d1) `mappend` (a2,b2,c2,d2) =
96                 (a1 `mappend` a2, b1 `mappend` b2,
97                  c1 `mappend` c2, d1 `mappend` d2)
98
99 instance (Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) =>
100                 Monoid (a,b,c,d,e) where
101         mempty = (mempty, mempty, mempty, mempty, mempty)
102         (a1,b1,c1,d1,e1) `mappend` (a2,b2,c2,d2,e2) =
103                 (a1 `mappend` a2, b1 `mappend` b2, c1 `mappend` c2,
104                  d1 `mappend` d2, e1 `mappend` e2)
105
106 -- lexicographical ordering
107 instance Monoid Ordering where
108         mempty         = EQ
109         LT `mappend` _ = LT
110         EQ `mappend` y = y
111         GT `mappend` _ = GT
112
113 -- | The dual of a monoid, obtained by swapping the arguments of 'mappend'.
114 newtype Dual a = Dual { getDual :: a }
115         deriving (Eq, Ord, Read, Show, Bounded)
116
117 instance Monoid a => Monoid (Dual a) where
118         mempty = Dual mempty
119         Dual x `mappend` Dual y = Dual (y `mappend` x)
120
121 -- | The monoid of endomorphisms under composition.
122 newtype Endo a = Endo { appEndo :: a -> a }
123
124 instance Monoid (Endo a) where
125         mempty = Endo id
126         Endo f `mappend` Endo g = Endo (f . g)
127
128 -- | Boolean monoid under conjunction.
129 newtype All = All { getAll :: Bool }
130         deriving (Eq, Ord, Read, Show, Bounded)
131
132 instance Monoid All where
133         mempty = All True
134         All x `mappend` All y = All (x && y)
135
136 -- | Boolean monoid under disjunction.
137 newtype Any = Any { getAny :: Bool }
138         deriving (Eq, Ord, Read, Show, Bounded)
139
140 instance Monoid Any where
141         mempty = Any False
142         Any x `mappend` Any y = Any (x || y)
143
144 -- | Monoid under addition.
145 newtype Sum a = Sum { getSum :: a }
146         deriving (Eq, Ord, Read, Show, Bounded)
147
148 instance Num a => Monoid (Sum a) where
149         mempty = Sum 0
150         Sum x `mappend` Sum y = Sum (x + y)
151
152 -- | Monoid under multiplication.
153 newtype Product a = Product { getProduct :: a }
154         deriving (Eq, Ord, Read, Show, Bounded)
155
156 instance Num a => Monoid (Product a) where
157         mempty = Product 1
158         Product x `mappend` Product y = Product (x * y)
159
160 -- $MaybeExamples
161 -- To implement @find@ or @findLast@ on any 'Foldable':
162 --
163 -- @
164 -- findLast :: Foldable t => (a -> Bool) -> t a -> Maybe a
165 -- findLast pred = getLast . foldMap (\x -> if pred x
166 --                                            then Last (Just x)
167 --                                            else Last Nothing)
168 -- @
169 --
170 -- Much of Data.Map's interface can be implemented with
171 -- Data.Map.alter. Some of the rest can be implemented with a new
172 -- @alterA@ function and either 'First' or 'Last':
173 --
174 -- > alterA :: (Applicative f, Ord k) =>
175 -- >           (Maybe a -> f (Maybe a)) -> k -> Map k a -> f (Map k a)
176 -- >
177 -- > instance Monoid a => Applicative ((,) a)  -- from Control.Applicative
178 --
179 -- @
180 -- insertLookupWithKey :: Ord k => (k -> v -> v -> v) -> k -> v
181 --                     -> Map k v -> (Maybe v, Map k v)
182 -- insertLookupWithKey combine key value =
183 --   Arrow.first getFirst . alterA doChange key
184 --   where
185 --   doChange Nothing = (First Nothing, Just value)
186 --   doChange (Just oldValue) =
187 --     (First (Just oldValue),
188 --      Just (combine key value oldValue))
189 -- @
190
191 -- | Lift a semigroup into 'Maybe' forming a 'Monoid' according to
192 -- <http://en.wikipedia.org/wiki/Monoid>: \"Any semigroup @S@ may be
193 -- turned into a monoid simply by adjoining an element @e@ not in @S@
194 -- and defining @e*e = e@ and @e*s = s = s*e@ for all @s ∈ S@.\" Since
195 -- there is no \"Semigroup\" typeclass providing just 'mappend', we
196 -- use 'Monoid' instead.
197 instance Monoid a => Monoid (Maybe a) where
198   mempty = Nothing
199   Nothing `mappend` m = m
200   m `mappend` Nothing = m
201   Just m1 `mappend` Just m2 = Just (m1 `mappend` m2)
202
203
204 -- | Maybe monoid returning the leftmost non-Nothing value.
205 newtype First a = First { getFirst :: Maybe a }
206 #ifndef __HADDOCK__
207         deriving (Eq, Ord, Read, Show)
208 #else  /* __HADDOCK__ */
209 instance Eq a => Eq (First a)
210 instance Ord a => Ord (First a)
211 instance Read a => Read (First a)
212 instance Show a => Show (First a)
213 #endif
214
215 instance Monoid (First a) where
216         mempty = First Nothing
217         r@(First (Just _)) `mappend` _ = r
218         First Nothing `mappend` r = r
219
220 -- | Maybe monoid returning the rightmost non-Nothing value.
221 newtype Last a = Last { getLast :: Maybe a }
222 #ifndef __HADDOCK__
223         deriving (Eq, Ord, Read, Show)
224 #else  /* __HADDOCK__ */
225 instance Eq a => Eq (Last a)
226 instance Ord a => Ord (Last a)
227 instance Read a => Read (Last a)
228 instance Show a => Show (Last a)
229 #endif
230
231 instance Monoid (Last a) where
232         mempty = Last Nothing
233         _ `mappend` r@(Last (Just _)) = r
234         r `mappend` Last Nothing = r
235
236 {-
237 {--------------------------------------------------------------------
238   Testing
239 --------------------------------------------------------------------}
240 instance Arbitrary a => Arbitrary (Maybe a) where
241   arbitrary = oneof [return Nothing, Just `fmap` arbitrary]
242
243 prop_mconcatMaybe :: [Maybe [Int]] -> Bool
244 prop_mconcatMaybe x =
245   fromMaybe [] (mconcat x) == mconcat (catMaybes x)
246
247 prop_mconcatFirst :: [Maybe Int] -> Bool
248 prop_mconcatFirst x =
249   getFirst (mconcat (map First x)) == listToMaybe (catMaybes x)
250 prop_mconcatLast :: [Maybe Int] -> Bool
251 prop_mconcatLast x =
252   getLast (mconcat (map Last x)) == listLastToMaybe (catMaybes x)
253         where listLastToMaybe [] = Nothing
254               listLastToMaybe lst = Just (last lst)
255 -- -}