[commit: ghc] wip/generics-propeq-conservative: Make constructor metadata parametrized (with intended parameter <- datatype) (0a8e6fc)
git at git.haskell.org
git at git.haskell.org
Fri Sep 19 01:55:27 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/generics-propeq-conservative
Link : http://ghc.haskell.org/trac/ghc/changeset/0a8e6fc97b2f7a944bc1723b2041cea4880dd5c2/ghc
>---------------------------------------------------------------
commit 0a8e6fc97b2f7a944bc1723b2041cea4880dd5c2
Author: Gabor Greif <ggreif at gmail.com>
Date: Mon Sep 1 23:52:01 2014 +0200
Make constructor metadata parametrized (with intended parameter <- datatype)
>---------------------------------------------------------------
0a8e6fc97b2f7a944bc1723b2041cea4880dd5c2
libraries/base/GHC/Generics.hs | 25 +++++++++++++------------
1 file changed, 13 insertions(+), 12 deletions(-)
diff --git a/libraries/base/GHC/Generics.hs b/libraries/base/GHC/Generics.hs
index c732a65..c8a69d6 100644
--- a/libraries/base/GHC/Generics.hs
+++ b/libraries/base/GHC/Generics.hs
@@ -7,6 +7,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE DeriveGeneric #-}
+{-# LANGUAGE FlexibleInstances #-}
-----------------------------------------------------------------------------
-- |
@@ -768,68 +769,68 @@ deriving instance Generic1 ((,,,,,,) a b c d e f)
-- Int
data D_Int
-data C_Int
+data C_Int d
instance Datatype D_Int where
datatypeName _ = "Int"
moduleName _ = "GHC.Int"
-instance Constructor C_Int where
+instance Constructor (C_Int D_Int) where
conName _ = "" -- JPM: I'm not sure this is the right implementation...
instance Generic Int where
- type Rep Int = D1 D_Int (C1 C_Int (S1 NoSelector (Rec0 Int)))
+ type Rep Int = D1 D_Int (C1 (C_Int D_Int) (S1 NoSelector (Rec0 Int)))
from x = M1 (M1 (M1 (K1 x)))
to (M1 (M1 (M1 (K1 x)))) = x
-- Float
data D_Float
-data C_Float
+data C_Float d
instance Datatype D_Float where
datatypeName _ = "Float"
moduleName _ = "GHC.Float"
-instance Constructor C_Float where
+instance Constructor (C_Float D_Float) where
conName _ = "" -- JPM: I'm not sure this is the right implementation...
instance Generic Float where
- type Rep Float = D1 D_Float (C1 C_Float (S1 NoSelector (Rec0 Float)))
+ type Rep Float = D1 D_Float (C1 (C_Float D_Float) (S1 NoSelector (Rec0 Float)))
from x = M1 (M1 (M1 (K1 x)))
to (M1 (M1 (M1 (K1 x)))) = x
-- Double
data D_Double
-data C_Double
+data C_Double d
instance Datatype D_Double where
datatypeName _ = "Double"
moduleName _ = "GHC.Float"
-instance Constructor C_Double where
+instance Constructor (C_Double D_Double) where
conName _ = "" -- JPM: I'm not sure this is the right implementation...
instance Generic Double where
- type Rep Double = D1 D_Double (C1 C_Double (S1 NoSelector (Rec0 Double)))
+ type Rep Double = D1 D_Double (C1 (C_Double D_Double) (S1 NoSelector (Rec0 Double)))
from x = M1 (M1 (M1 (K1 x)))
to (M1 (M1 (M1 (K1 x)))) = x
-- Char
data D_Char
-data C_Char
+data C_Char d
instance Datatype D_Char where
datatypeName _ = "Char"
moduleName _ = "GHC.Base"
-instance Constructor C_Char where
+instance Constructor (C_Char D_Char) where
conName _ = "" -- JPM: I'm not sure this is the right implementation...
instance Generic Char where
- type Rep Char = D1 D_Char (C1 C_Char (S1 NoSelector (Rec0 Char)))
+ type Rep Char = D1 D_Char (C1 (C_Char D_Char) (S1 NoSelector (Rec0 Char)))
from x = M1 (M1 (M1 (K1 x)))
to (M1 (M1 (M1 (K1 x)))) = x
More information about the ghc-commits
mailing list