1{-
2
3Copyright (c) 2013 Lukas Mai
4
5All rights reserved.
6
7Redistribution and use in source and binary forms, with or without modification,
8are permitted provided that the following conditions are met:
9
10* Redistributions of source code must retain the above copyright notice, this
11  list of conditions and the following disclaimer.
12* Redistributions in binary form must reproduce the above copyright notice,
13  this list of conditions and the following disclaimer in the documentation
14  and/or other materials provided with the distribution.
15* Neither the name of the author nor the names of his contributors
16  may be used to endorse or promote products derived from this software
17  without specific prior written permission.
18
19THIS SOFTWARE IS PROVIDED BY LUKAS MAI AND CONTRIBUTORS "AS IS" AND ANY
20EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
21WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
22DISCLAIMED. IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE FOR ANY
23DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES
24(INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
25LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON
26ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
27(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS
28SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
29
30-}
31
32{-# LANGUAGE CPP #-}
33
34#define HAVE_GHC_GENERICS (__GLASGOW_HASKELL__ >= 704)
35
36#if HAVE_GHC_GENERICS
37{-# LANGUAGE DefaultSignatures, TypeOperators, FlexibleContexts #-}
38#endif
39
40module Data.Default.Class (
41-- | This module defines a class for types with a default value.
42-- It also defines 'Default' instances for the types 'Int', 'Int8',
43-- 'Int16', 'Int32', 'Int64', 'Word', 'Word8', 'Word16', 'Word32', 'Word64',
44-- 'Integer', 'Float', 'Double', 'Ratio', 'Complex', 'CShort', 'CUShort',
45-- 'CInt', 'CUInt', 'CLong', 'CULong', 'CLLong', 'CULLong', 'CPtrdiff',
46-- 'CSize', 'CSigAtomic', 'CIntPtr', 'CUIntPtr', 'CIntMax', 'CUIntMax',
47-- 'CClock', 'CTime', 'CUSeconds', 'CSUSeconds', 'CFloat', 'CDouble', '(->)',
48-- 'IO', 'Maybe', '()', '[]', 'Ordering', 'Any', 'All', 'Last', 'First', 'Sum',
49-- 'Product', 'Endo', 'Dual', and tuples.
50    Default(..)
51) where
52
53import Data.Int
54import Data.Word
55import Data.Monoid
56import Data.Ratio
57import Data.Complex
58import Foreign.C.Types
59
60#if HAVE_GHC_GENERICS
61import GHC.Generics
62
63class GDefault f where
64    gdef :: f a
65
66instance GDefault U1 where
67    gdef = U1
68
69instance (Default a) => GDefault (K1 i a) where
70    gdef = K1 def
71
72instance (GDefault a, GDefault b) => GDefault (a :*: b) where
73    gdef = gdef :*: gdef
74
75instance (GDefault a) => GDefault (M1 i c a) where
76    gdef = M1 gdef
77#endif
78
79-- | A class for types with a default value.
80class Default a where
81    -- | The default value for this type.
82    def :: a
83
84#if HAVE_GHC_GENERICS
85    default def :: (Generic a, GDefault (Rep a)) => a
86    def = to gdef
87#endif
88
89instance Default Int where def = 0
90instance Default Int8 where def = 0
91instance Default Int16 where def = 0
92instance Default Int32 where def = 0
93instance Default Int64 where def = 0
94instance Default Word where def = 0
95instance Default Word8 where def = 0
96instance Default Word16 where def = 0
97instance Default Word32 where def = 0
98instance Default Word64 where def = 0
99instance Default Integer where def = 0
100instance Default Float where def = 0
101instance Default Double where def = 0
102instance (Integral a) => Default (Ratio a) where def = 0
103instance (Default a, RealFloat a) => Default (Complex a) where def = def :+ def
104
105instance Default CShort     where def = 0
106instance Default CUShort    where def = 0
107instance Default CInt       where def = 0
108instance Default CUInt      where def = 0
109instance Default CLong      where def = 0
110instance Default CULong     where def = 0
111instance Default CLLong     where def = 0
112instance Default CULLong    where def = 0
113instance Default CPtrdiff   where def = 0
114instance Default CSize      where def = 0
115instance Default CSigAtomic where def = 0
116instance Default CIntPtr    where def = 0
117instance Default CUIntPtr   where def = 0
118instance Default CIntMax    where def = 0
119instance Default CUIntMax   where def = 0
120instance Default CClock     where def = 0
121instance Default CTime      where def = 0
122#if MIN_VERSION_base(4, 4, 0)
123instance Default CUSeconds  where def = 0
124instance Default CSUSeconds where def = 0
125#endif
126instance Default CFloat     where def = 0
127instance Default CDouble    where def = 0
128
129instance (Default r) => Default (e -> r) where def = const def
130instance (Default a) => Default (IO a) where def = return def
131
132instance Default (Maybe a) where def = Nothing
133
134instance Default () where def = mempty
135instance Default [a] where def = mempty
136instance Default Ordering where def = mempty
137instance Default Any where def = mempty
138instance Default All where def = mempty
139instance Default (Last a) where def = mempty
140instance Default (First a) where def = mempty
141instance (Num a) => Default (Sum a) where def = mempty
142instance (Num a) => Default (Product a) where def = mempty
143instance Default (Endo a) where def = mempty
144
145instance (Default a) => Default (Dual a) where def = Dual def
146instance (Default a, Default b) => Default (a, b) where def = (def, def)
147instance (Default a, Default b, Default c) => Default (a, b, c) where def = (def, def, def)
148instance (Default a, Default b, Default c, Default d) => Default (a, b, c, d) where def = (def, def, def, def)
149instance (Default a, Default b, Default c, Default d, Default e) => Default (a, b, c, d, e) where def = (def, def, def, def, def)
150instance (Default a, Default b, Default c, Default d, Default e, Default f) => Default (a, b, c, d, e, f) where def = (def, def, def, def, def, def)
151instance (Default a, Default b, Default c, Default d, Default e, Default f, Default g) => Default (a, b, c, d, e, f, g) where def = (def, def, def, def, def, def, def)
152