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