[project @ 2005-11-17 15:54:17 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         Dual(..),
24         Endo(..),
25         All(..),
26         Any(..),
27         Sum(..),
28         Product(..)
29   ) where
30
31 import Prelude
32
33 -- ---------------------------------------------------------------------------
34 -- | The monoid class.
35 -- A minimal complete definition must supply 'mempty' and 'mappend',
36 -- and these should satisfy the monoid laws.
37
38 class Monoid a where
39         mempty  :: a
40         -- ^ Identity of 'mappend'
41         mappend :: a -> a -> a
42         -- ^ An associative operation
43         mconcat :: [a] -> a
44
45         -- ^ Fold a list using the monoid.
46         -- For most types, the default definition for 'mconcat' will be
47         -- used, but the function is included in the class definition so
48         -- that an optimized version can be provided for specific types.
49
50         mconcat = foldr mappend mempty
51
52 -- Monoid instances.
53
54 instance Monoid [a] where
55         mempty  = []
56         mappend = (++)
57
58 instance Monoid b => Monoid (a -> b) where
59         mempty _ = mempty
60         mappend f g x = f x `mappend` g x
61
62 instance Monoid () where
63         -- Should it be strict?
64         mempty        = ()
65         _ `mappend` _ = ()
66         mconcat _     = ()
67
68 instance (Monoid a, Monoid b) => Monoid (a,b) where
69         mempty = (mempty, mempty)
70         (a1,b1) `mappend` (a2,b2) =
71                 (a1 `mappend` a2, b1 `mappend` b2)
72
73 instance (Monoid a, Monoid b, Monoid c) => Monoid (a,b,c) where
74         mempty = (mempty, mempty, mempty)
75         (a1,b1,c1) `mappend` (a2,b2,c2) =
76                 (a1 `mappend` a2, b1 `mappend` b2, c1 `mappend` c2)
77
78 instance (Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a,b,c,d) where
79         mempty = (mempty, mempty, mempty, mempty)
80         (a1,b1,c1,d1) `mappend` (a2,b2,c2,d2) =
81                 (a1 `mappend` a2, b1 `mappend` b2,
82                  c1 `mappend` c2, d1 `mappend` d2)
83
84 instance (Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) =>
85                 Monoid (a,b,c,d,e) where
86         mempty = (mempty, mempty, mempty, mempty, mempty)
87         (a1,b1,c1,d1,e1) `mappend` (a2,b2,c2,d2,e2) =
88                 (a1 `mappend` a2, b1 `mappend` b2, c1 `mappend` c2,
89                  d1 `mappend` d2, e1 `mappend` e2)
90
91 -- lexicographical ordering
92 instance Monoid Ordering where
93         mempty         = EQ
94         LT `mappend` _ = LT
95         EQ `mappend` y = y
96         GT `mappend` _ = GT
97
98 -- | The dual of a monoid, obtained by swapping the arguments of 'mappend'.
99 newtype Dual a = Dual { getDual :: a }
100
101 instance Monoid a => Monoid (Dual a) where
102         mempty = Dual mempty
103         Dual x `mappend` Dual y = Dual (y `mappend` x)
104
105 -- | The monoid of endomorphisms under composition.
106 newtype Endo a = Endo { appEndo :: a -> a }
107
108 instance Monoid (Endo a) where
109         mempty = Endo id
110         Endo f `mappend` Endo g = Endo (f . g)
111
112 -- | Boolean monoid under conjunction.
113 newtype All = All { getAll :: Bool }
114
115 instance Monoid All where
116         mempty = All True
117         All x `mappend` All y = All (x && y)
118
119 -- | Boolean monoid under disjunction.
120 newtype Any = Any { getAny :: Bool }
121
122 instance Monoid Any where
123         mempty = Any False
124         Any x `mappend` Any y = Any (x || y)
125
126 -- | Monoid under addition.
127 newtype Sum a = Sum { getSum :: a }
128
129 instance Num a => Monoid (Sum a) where
130         mempty = Sum 0
131         Sum x `mappend` Sum y = Sum (x + y)
132
133 -- | Monoid under multiplication.
134 newtype Product a = Product { getProduct :: a }
135
136 instance Num a => Monoid (Product a) where
137         mempty = Product 1
138         Product x `mappend` Product y = Product (x * y)