[project @ 2005-10-25 09:11:25 by ross]
[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 -- The Monoid class with various general-purpose instances.
13 --
14 --        Inspired by the paper
15 --        /Functional Programming with Overloading and
16 --            Higher-Order Polymorphism/, 
17 --          Mark P Jones (<http://www.cse.ogi.edu/~mpj/>)
18 --                Advanced School of Functional Programming, 1995.
19 -----------------------------------------------------------------------------
20
21 module Data.Monoid (
22         Monoid(..),
23         Endo(..),
24         Dual(..),
25         Sum(..),
26         Product(..)
27   ) where
28
29 import Prelude
30 import Data.Map ( Map )
31 import qualified Data.Map as Map hiding ( Map )
32 import Data.IntMap ( IntMap )
33 import qualified Data.IntMap as IntMap hiding ( IntMap )
34 import Data.Set ( Set )
35 import qualified Data.Set as Set hiding ( Set )
36 import Data.IntSet ( IntSet )
37 import qualified Data.IntSet as IntSet hiding ( IntSet )
38
39 -- ---------------------------------------------------------------------------
40 -- | The monoid class.
41 -- A minimal complete definition must supply 'mempty' and 'mappend',
42 -- and these should satisfy the monoid laws.
43
44 class Monoid a where
45         mempty  :: a
46         -- ^ Identity of 'mappend'
47         mappend :: a -> a -> a
48         -- ^ An associative operation
49         mconcat :: [a] -> a
50
51         -- ^ Fold a list using the monoid.
52         -- For most types, the default definition for 'mconcat' will be
53         -- used, but the function is included in the class definition so
54         -- that an optimized version can be provided for specific types.
55
56         mconcat = foldr mappend mempty
57
58 -- Monoid instances.
59
60 instance Monoid [a] where
61         mempty  = []
62         mappend = (++)
63
64 instance Monoid b => Monoid (a -> b) where
65         mempty _ = mempty
66         mappend f g x = f x `mappend` g x
67
68 instance Monoid () where
69         -- Should it be strict?
70         mempty        = ()
71         _ `mappend` _ = ()
72         mconcat _     = ()
73
74 instance (Monoid a, Monoid b) => Monoid (a,b) where
75         mempty = (mempty, mempty)
76         (a1,b1) `mappend` (a2,b2) =
77                 (a1 `mappend` a2, b1 `mappend` b2)
78
79 instance (Monoid a, Monoid b, Monoid c) => Monoid (a,b,c) where
80         mempty = (mempty, mempty, mempty)
81         (a1,b1,c1) `mappend` (a2,b2,c2) =
82                 (a1 `mappend` a2, b1 `mappend` b2, c1 `mappend` c2)
83
84 instance (Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a,b,c,d) where
85         mempty = (mempty, mempty, mempty, mempty)
86         (a1,b1,c1,d1) `mappend` (a2,b2,c2,d2) =
87                 (a1 `mappend` a2, b1 `mappend` b2,
88                  c1 `mappend` c2, d1 `mappend` d2)
89
90 instance (Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) =>
91                 Monoid (a,b,c,d,e) where
92         mempty = (mempty, mempty, mempty, mempty, mempty)
93         (a1,b1,c1,d1,e1) `mappend` (a2,b2,c2,d2,e2) =
94                 (a1 `mappend` a2, b1 `mappend` b2, c1 `mappend` c2,
95                  d1 `mappend` d2, e1 `mappend` e2)
96
97 -- lexicographical ordering
98 instance Monoid Ordering where
99         mempty         = EQ
100         LT `mappend` _ = LT
101         EQ `mappend` y = y
102         GT `mappend` _ = GT
103
104 -- | The monoid of endomorphisms under composition.
105 newtype Endo a = Endo { appEndo :: a -> a }
106
107 instance Monoid (Endo a) where
108         mempty = Endo id
109         Endo f `mappend` Endo g = Endo (f . g)
110
111 -- | The dual of a monoid, obtained by swapping the arguments of 'mappend'.
112 newtype Dual a = Dual { getDual :: a }
113
114 instance Monoid a => Monoid (Dual a) where
115         mempty = Dual mempty
116         Dual x `mappend` Dual y = Dual (y `mappend` x)
117
118 -- | Monoid under addition.
119 newtype Sum a = Sum { getSum :: a }
120
121 instance Num a => Monoid (Sum a) where
122         mempty = Sum 0
123         Sum x `mappend` Sum y = Sum (x + y)
124
125 -- | Monoid under multiplication.
126 newtype Product a = Product { getProduct :: a }
127
128 instance Num a => Monoid (Product a) where
129         mempty = Product 1
130         Product x `mappend` Product y = Product (x * y)
131
132 instance (Ord k) => Monoid (Map k v) where
133     mempty  = Map.empty
134     mappend = Map.union
135     mconcat = Map.unions
136
137 instance Ord a => Monoid (IntMap a) where
138     mempty  = IntMap.empty
139     mappend = IntMap.union
140     mconcat = IntMap.unions
141
142 instance Ord a => Monoid (Set a) where
143     mempty  = Set.empty
144     mappend = Set.union
145     mconcat = Set.unions
146
147 instance Monoid IntSet where
148     mempty  = IntSet.empty
149     mappend = IntSet.union
150     mconcat = IntSet.unions