[commit: ghc] wip/generics-propeq: Equip D_Int with a Symbol at the type level (79cf130)

git at git.haskell.org git at git.haskell.org
Sat Jun 28 11:51:15 UTC 2014


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/generics-propeq
Link       : http://ghc.haskell.org/trac/ghc/changeset/79cf13006b7f50d1bcf5077e97b1e329619b5e3a/ghc

>---------------------------------------------------------------

commit 79cf13006b7f50d1bcf5077e97b1e329619b5e3a
Author: Gabor Greif <ggreif at gmail.com>
Date:   Wed Jun 25 12:59:25 2014 +0200

    Equip D_Int with a Symbol at the type level


>---------------------------------------------------------------

79cf13006b7f50d1bcf5077e97b1e329619b5e3a
 libraries/base/GHC/Generics.hs | 9 ++++++---
 1 file changed, 6 insertions(+), 3 deletions(-)

diff --git a/libraries/base/GHC/Generics.hs b/libraries/base/GHC/Generics.hs
index 1c81858..683c168 100644
--- a/libraries/base/GHC/Generics.hs
+++ b/libraries/base/GHC/Generics.hs
@@ -7,6 +7,8 @@
 {-# LANGUAGE TypeFamilies           #-}
 {-# LANGUAGE StandaloneDeriving     #-}
 {-# LANGUAGE DeriveGeneric          #-}
+{-# LANGUAGE DataKinds              #-}
+{-# LANGUAGE FlexibleInstances      #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -562,6 +564,7 @@ module GHC.Generics  (
 
 -- We use some base types
 import GHC.Types
+import GHC.TypeLits
 import Data.Maybe ( Maybe(..) )
 import Data.Either ( Either(..) )
 
@@ -750,10 +753,10 @@ deriving instance Generic1 ((,,,,,,) a b c d e f)
 --------------------------------------------------------------------------------
 
 -- Int
-data D_Int
+data D_Int (name :: Symbol)
 data C_Int
 
-instance Datatype D_Int where
+instance Datatype (D_Int "Int") where
   datatypeName _ = "Int"
   moduleName   _ = "GHC.Int"
 
@@ -761,7 +764,7 @@ instance Constructor C_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 "Int") (C1 C_Int (S1 NoSelector (Rec0 Int)))
   from x = M1 (M1 (M1 (K1 x)))
   to (M1 (M1 (M1 (K1 x)))) = x
 



More information about the ghc-commits mailing list