Skip to content

Commit f9b2d3d

Browse files
committed
expose internal GDefault type
1 parent dcd9f49 commit f9b2d3d

File tree

3 files changed

+174
-124
lines changed

3 files changed

+174
-124
lines changed

Data/Default.hs

Lines changed: 1 addition & 123 deletions
Original file line numberDiff line numberDiff line change
@@ -33,9 +33,6 @@ OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
3333
3434
-}
3535

36-
{-# LANGUAGE CPP #-}
37-
{-# LANGUAGE DefaultSignatures, TypeOperators, FlexibleContexts #-}
38-
3936
{-|
4037
Module : Data.Default
4138
Description : A class for types with a default value.
@@ -48,123 +45,4 @@ module Data.Default (
4845
Default(..)
4946
) where
5047

51-
import Data.Int
52-
import Data.Word
53-
import Data.Monoid
54-
import Data.Ratio
55-
import Data.Complex
56-
import Data.Fixed
57-
import Foreign.C.Types
58-
import Data.Proxy
59-
import Data.Functor.Identity
60-
import Control.Applicative (Const(..))
61-
#if MIN_VERSION_base(4, 16, 0)
62-
import Data.Tuple
63-
#endif
64-
import qualified Data.Set as S
65-
import qualified Data.Map as M
66-
import Data.IntMap (IntMap)
67-
import Data.IntSet (IntSet)
68-
import Data.Sequence (Seq)
69-
import Data.Tree (Tree(..))
70-
71-
import GHC.Generics
72-
73-
class GDefault f where
74-
gdef :: f a
75-
76-
instance GDefault U1 where
77-
gdef = U1
78-
79-
instance (Default a) => GDefault (K1 i a) where
80-
gdef = K1 def
81-
82-
instance (GDefault a, GDefault b) => GDefault (a :*: b) where
83-
gdef = gdef :*: gdef
84-
85-
instance (GDefault a) => GDefault (a :+: b) where
86-
gdef = L1 gdef
87-
88-
instance (GDefault a) => GDefault (M1 i c a) where
89-
gdef = M1 gdef
90-
91-
-- | A class for types with a default value.
92-
class Default a where
93-
-- | The default value for this type.
94-
def :: a
95-
96-
default def :: (Generic a, GDefault (Rep a)) => a
97-
def = to gdef
98-
99-
instance Default Int where def = 0
100-
instance Default Int8 where def = 0
101-
instance Default Int16 where def = 0
102-
instance Default Int32 where def = 0
103-
instance Default Int64 where def = 0
104-
instance Default Word where def = 0
105-
instance Default Word8 where def = 0
106-
instance Default Word16 where def = 0
107-
instance Default Word32 where def = 0
108-
instance Default Word64 where def = 0
109-
instance Default Integer where def = 0
110-
instance Default Float where def = 0
111-
instance Default Double where def = 0
112-
instance (Integral a) => Default (Ratio a) where def = 0
113-
instance (Default a, RealFloat a) => Default (Complex a) where def = def :+ def
114-
instance (HasResolution a) => Default (Fixed a) where def = 0
115-
116-
instance Default CShort where def = 0
117-
instance Default CUShort where def = 0
118-
instance Default CInt where def = 0
119-
instance Default CUInt where def = 0
120-
instance Default CLong where def = 0
121-
instance Default CULong where def = 0
122-
instance Default CLLong where def = 0
123-
instance Default CULLong where def = 0
124-
instance Default CPtrdiff where def = 0
125-
instance Default CSize where def = 0
126-
instance Default CSigAtomic where def = 0
127-
instance Default CIntPtr where def = 0
128-
instance Default CUIntPtr where def = 0
129-
instance Default CIntMax where def = 0
130-
instance Default CUIntMax where def = 0
131-
instance Default CClock where def = 0
132-
instance Default CTime where def = 0
133-
instance Default CUSeconds where def = 0
134-
instance Default CSUSeconds where def = 0
135-
instance Default CFloat where def = 0
136-
instance Default CDouble where def = 0
137-
138-
instance Default (Maybe a) where def = Nothing
139-
instance (Default a) => Default (Identity a) where def = Identity def
140-
instance (Default a) => Default (Const a b) where def = Const def
141-
142-
instance Default () where def = mempty
143-
instance Default [a] where def = mempty
144-
instance Default Ordering where def = mempty
145-
instance Default Any where def = mempty
146-
instance Default All where def = mempty
147-
instance Default (Last a) where def = mempty
148-
instance Default (First a) where def = mempty
149-
instance (Num a) => Default (Sum a) where def = mempty
150-
instance (Num a) => Default (Product a) where def = mempty
151-
instance Default (Endo a) where def = mempty
152-
instance Default (Proxy a) where def = mempty
153-
#if MIN_VERSION_base(4, 16, 0)
154-
instance (Default a) => Default (Solo a) where def = pure def
155-
#endif
156-
157-
instance (Default a) => Default (Dual a) where def = Dual def
158-
instance (Default a, Default b) => Default (a, b) where def = (def, def)
159-
instance (Default a, Default b, Default c) => Default (a, b, c) where def = (def, def, def)
160-
instance (Default a, Default b, Default c, Default d) => Default (a, b, c, d) where def = (def, def, def, def)
161-
instance (Default a, Default b, Default c, Default d, Default e) => Default (a, b, c, d, e) where def = (def, def, def, def, def)
162-
instance (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)
163-
instance (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)
164-
165-
instance Default (S.Set v) where def = S.empty
166-
instance Default (M.Map k v) where def = M.empty
167-
instance Default (IntMap v) where def = mempty
168-
instance Default IntSet where def = mempty
169-
instance Default (Seq a) where def = mempty
170-
instance (Default a) => Default (Tree a) where def = Node def []
48+
import Data.Default.Internal

Data/Default/Internal.hs

Lines changed: 172 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,172 @@
1+
{-
2+
3+
Copyright (c) 2013, Lukas Mai
4+
5+
All rights reserved.
6+
7+
Redistribution and use in source and binary forms, with or without
8+
modification, are permitted provided that the following conditions are met:
9+
10+
* Redistributions of source code must retain the above copyright
11+
notice, this list of conditions and the following disclaimer.
12+
13+
* Redistributions in binary form must reproduce the above
14+
copyright notice, this list of conditions and the following
15+
disclaimer in the documentation and/or other materials provided
16+
with the distribution.
17+
18+
* Neither the name of Lukas Mai nor the names of other
19+
contributors may be used to endorse or promote products derived
20+
from this software without specific prior written permission.
21+
22+
THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
23+
"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
24+
LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
25+
A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
26+
OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
27+
SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
28+
LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
29+
DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
30+
THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
31+
(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
32+
OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
33+
34+
-}
35+
36+
{-# LANGUAGE CPP #-}
37+
{-# LANGUAGE DefaultSignatures, TypeOperators, FlexibleContexts #-}
38+
39+
{-|
40+
Module : Data.Default.Internal
41+
Description : Implementation details.
42+
43+
Nothing to see here.
44+
-}
45+
module Data.Default.Internal (Default(..), GDefault(..)) where
46+
47+
import Data.Int
48+
import Data.Word
49+
import Data.Monoid
50+
import Data.Ratio
51+
import Data.Complex
52+
import Data.Fixed
53+
import Foreign.C.Types
54+
import Data.Proxy
55+
import Data.Functor.Identity
56+
import Control.Applicative (Const(..))
57+
#if MIN_VERSION_base(4, 16, 0)
58+
import Data.Tuple
59+
#endif
60+
import qualified Data.Set as S
61+
import qualified Data.Map as M
62+
import Data.IntMap (IntMap)
63+
import Data.IntSet (IntSet)
64+
import Data.Sequence (Seq)
65+
import Data.Tree (Tree(..))
66+
67+
import GHC.Generics
68+
69+
-- | Defaults, generically.
70+
class GDefault f where
71+
gdef :: f a
72+
73+
-- | A nullary constructor is its own default.
74+
instance GDefault U1 where
75+
gdef = U1
76+
77+
-- | A unary constructor wraps the default value of the argument type.
78+
instance (Default a) => GDefault (K1 i a) where
79+
gdef = K1 def
80+
81+
-- | Default of products = product of defaults.
82+
instance (GDefault a, GDefault b) => GDefault (a :*: b) where
83+
gdef = gdef :*: gdef
84+
85+
-- | For sums, we arbitrarily choose the left side.
86+
instance (GDefault a) => GDefault (a :+: b) where
87+
gdef = L1 gdef
88+
89+
-- | Default of wrapper = wrapper of default.
90+
instance (GDefault a) => GDefault (M1 i c a) where
91+
gdef = M1 gdef
92+
93+
-- | A class for types with a default value.
94+
class Default a where
95+
-- | The default value for this type.
96+
def :: a
97+
98+
default def :: (Generic a, GDefault (Rep a)) => a
99+
def = to gdef
100+
101+
instance Default Int where def = 0
102+
instance Default Int8 where def = 0
103+
instance Default Int16 where def = 0
104+
instance Default Int32 where def = 0
105+
instance Default Int64 where def = 0
106+
instance Default Word where def = 0
107+
instance Default Word8 where def = 0
108+
instance Default Word16 where def = 0
109+
instance Default Word32 where def = 0
110+
instance Default Word64 where def = 0
111+
instance Default Integer where def = 0
112+
instance Default Float where def = 0
113+
instance Default Double where def = 0
114+
instance (Integral a) => Default (Ratio a) where def = 0
115+
instance (Default a, RealFloat a) => Default (Complex a) where def = def :+ def
116+
instance (HasResolution a) => Default (Fixed a) where def = 0
117+
118+
instance Default CShort where def = 0
119+
instance Default CUShort where def = 0
120+
instance Default CInt where def = 0
121+
instance Default CUInt where def = 0
122+
instance Default CLong where def = 0
123+
instance Default CULong where def = 0
124+
instance Default CLLong where def = 0
125+
instance Default CULLong where def = 0
126+
instance Default CPtrdiff where def = 0
127+
instance Default CSize where def = 0
128+
instance Default CSigAtomic where def = 0
129+
instance Default CIntPtr where def = 0
130+
instance Default CUIntPtr where def = 0
131+
instance Default CIntMax where def = 0
132+
instance Default CUIntMax where def = 0
133+
instance Default CClock where def = 0
134+
instance Default CTime where def = 0
135+
instance Default CUSeconds where def = 0
136+
instance Default CSUSeconds where def = 0
137+
instance Default CFloat where def = 0
138+
instance Default CDouble where def = 0
139+
140+
instance Default (Maybe a) where def = Nothing
141+
instance (Default a) => Default (Identity a) where def = Identity def
142+
instance (Default a) => Default (Const a b) where def = Const def
143+
144+
instance Default () where def = mempty
145+
instance Default [a] where def = mempty
146+
instance Default Ordering where def = mempty
147+
instance Default Any where def = mempty
148+
instance Default All where def = mempty
149+
instance Default (Last a) where def = mempty
150+
instance Default (First a) where def = mempty
151+
instance (Num a) => Default (Sum a) where def = mempty
152+
instance (Num a) => Default (Product a) where def = mempty
153+
instance Default (Endo a) where def = mempty
154+
instance Default (Proxy a) where def = mempty
155+
#if MIN_VERSION_base(4, 16, 0)
156+
instance (Default a) => Default (Solo a) where def = pure def
157+
#endif
158+
159+
instance (Default a) => Default (Dual a) where def = Dual def
160+
instance (Default a, Default b) => Default (a, b) where def = (def, def)
161+
instance (Default a, Default b, Default c) => Default (a, b, c) where def = (def, def, def)
162+
instance (Default a, Default b, Default c, Default d) => Default (a, b, c, d) where def = (def, def, def, def)
163+
instance (Default a, Default b, Default c, Default d, Default e) => Default (a, b, c, d, e) where def = (def, def, def, def, def)
164+
instance (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)
165+
instance (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)
166+
167+
instance Default (S.Set v) where def = S.empty
168+
instance Default (M.Map k v) where def = M.empty
169+
instance Default (IntMap v) where def = mempty
170+
instance Default IntSet where def = mempty
171+
instance Default (Seq a) where def = mempty
172+
instance (Default a) => Default (Tree a) where def = Node def []

data-default.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ source-repository head
2020

2121
library
2222
build-depends: base >=4.8 && <5, containers >=0.1 && <0.8
23-
exposed-modules: Data.Default
23+
exposed-modules: Data.Default, Data.Default.Internal
2424
default-language: Haskell98
2525

2626
test-suite test

0 commit comments

Comments
 (0)