summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorRyanGlScott <ryan.gl.scott@gmail.com>2015-08-29 12:23:31 +0200
committerBen Gamari <ben@smart-cactus.org>2015-08-29 13:08:17 +0200
commita6826c5d18675a783acce39352eea283e462bf8b (patch)
tree5116ae27d6ea81aea932e97ebe20c224aec1792e
parent15cb83d4e98c2c356bf0e3eb0df6d322755337bd (diff)
downloadhaskell-a6826c5d18675a783acce39352eea283e462bf8b.tar.gz
Make Generic (Proxy t) instance poly-kinded (fixes #10775)
This amounts to enabling PolyKinds in GHC.Generics. However, explicit kind signatures must be applied to the datatypes and typeclasses in GHC.Generics to ensure that the Core which TcGenGenerics generates is properly kinded. Several of the typeclasses in GHC.Generics could be poly-kinded, but this differential does not attempt to address this, since D493 already addresses this. Test Plan: ./validate Reviewers: hvr, austin, dreixel, bgamari Reviewed By: austin, dreixel, bgamari Subscribers: goldfire, thomie Differential Revision: https://phabricator.haskell.org/D1166 GHC Trac Issues: #10775
-rw-r--r--libraries/base/GHC/Generics.hs39
-rw-r--r--libraries/base/changelog.md2
2 files changed, 22 insertions, 19 deletions
diff --git a/libraries/base/GHC/Generics.hs b/libraries/base/GHC/Generics.hs
index 0b4ebc6488..d98533b5b2 100644
--- a/libraries/base/GHC/Generics.hs
+++ b/libraries/base/GHC/Generics.hs
@@ -7,6 +7,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE DeriveGeneric #-}
+{-# LANGUAGE PolyKinds #-}
-----------------------------------------------------------------------------
-- |
@@ -576,10 +577,10 @@ import Data.Proxy
--------------------------------------------------------------------------------
-- | Void: used for datatypes without constructors
-data V1 p
+data V1 (p :: *)
-- | Unit: used for constructors without arguments
-data U1 p = U1
+data U1 (p :: *) = U1
deriving (Eq, Ord, Read, Show, Generic)
-- | Used for marking occurrences of the parameter
@@ -587,30 +588,30 @@ newtype Par1 p = Par1 { unPar1 :: p }
deriving (Eq, Ord, Read, Show, Generic)
-- | Recursive calls of kind * -> *
-newtype Rec1 f p = Rec1 { unRec1 :: f p }
+newtype Rec1 f (p :: *) = Rec1 { unRec1 :: f p }
deriving (Eq, Ord, Read, Show, Generic)
-- | Constants, additional parameters and recursion of kind *
-newtype K1 i c p = K1 { unK1 :: c }
+newtype K1 (i :: *) c (p :: *) = K1 { unK1 :: c }
deriving (Eq, Ord, Read, Show, Generic)
-- | Meta-information (constructor names, etc.)
-newtype M1 i c f p = M1 { unM1 :: f p }
+newtype M1 (i :: *) (c :: *) f (p :: *) = M1 { unM1 :: f p }
deriving (Eq, Ord, Read, Show, Generic)
-- | Sums: encode choice between constructors
infixr 5 :+:
-data (:+:) f g p = L1 (f p) | R1 (g p)
+data (:+:) f g (p :: *) = L1 (f p) | R1 (g p)
deriving (Eq, Ord, Read, Show, Generic)
-- | Products: encode multiple arguments to constructors
infixr 6 :*:
-data (:*:) f g p = f p :*: g p
+data (:*:) f g (p :: *) = f p :*: g p
deriving (Eq, Ord, Read, Show, Generic)
-- | Composition of functors
infixr 7 :.:
-newtype (:.:) f g p = Comp1 { unComp1 :: f (g p) }
+newtype (:.:) f (g :: * -> *) (p :: *) = Comp1 { unComp1 :: f (g p) }
deriving (Eq, Ord, Read, Show, Generic)
-- | Tag for K1: recursion (of kind *)
@@ -643,22 +644,22 @@ type S1 = M1 S
-- | Class for datatypes that represent datatypes
-class Datatype d where
+class Datatype (d :: *) where
-- | The name of the datatype (unqualified)
- datatypeName :: t d (f :: * -> *) a -> [Char]
+ datatypeName :: t d (f :: * -> *) (a :: *) -> [Char]
-- | The fully-qualified name of the module where the type is declared
- moduleName :: t d (f :: * -> *) a -> [Char]
+ moduleName :: t d (f :: * -> *) (a :: *) -> [Char]
-- | The package name of the module where the type is declared
- packageName :: t d (f :: * -> *) a -> [Char]
+ packageName :: t d (f :: * -> *) (a :: *) -> [Char]
-- | Marks if the datatype is actually a newtype
- isNewtype :: t d (f :: * -> *) a -> Bool
+ isNewtype :: t d (f :: * -> *) (a :: *) -> Bool
isNewtype _ = False
-- | Class for datatypes that represent records
-class Selector s where
+class Selector (s :: *) where
-- | The name of the selector
- selName :: t s (f :: * -> *) a -> [Char]
+ selName :: t s (f :: * -> *) (a :: *) -> [Char]
-- | Used for constructor fields without a name
data NoSelector
@@ -666,16 +667,16 @@ data NoSelector
instance Selector NoSelector where selName _ = ""
-- | Class for datatypes that represent data constructors
-class Constructor c where
+class Constructor (c :: *) where
-- | The name of the constructor
- conName :: t c (f :: * -> *) a -> [Char]
+ conName :: t c (f :: * -> *) (a :: *) -> [Char]
-- | The fixity of the constructor
- conFixity :: t c (f :: * -> *) a -> Fixity
+ conFixity :: t c (f :: * -> *) (a :: *) -> Fixity
conFixity _ = Prefix
-- | Marks if this constructor is a record
- conIsRecord :: t c (f :: * -> *) a -> Bool
+ conIsRecord :: t c (f :: * -> *) (a :: *) -> Bool
conIsRecord _ = False
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index 9ceef87ded..51a1de9d58 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -56,6 +56,8 @@
* Made `PatternMatchFail`, `RecSelError`, `RecConError`, `RecUpdError`,
`NoMethodError`, and `AssertionFailed` newtypes (#10738)
+ * The `Generic` instance for `Proxy` is now poly-kinded (#10775)
+
## 4.8.1.0 *Jul 2015*
* Bundled with GHC 7.10.2