summaryrefslogtreecommitdiff
path: root/libraries/base/GHC/Generics.hs
diff options
context:
space:
mode:
authorBen Gamari <ben@smart-cactus.org>2020-05-09 15:49:07 -0400
committerMarge Bot <ben+marge-bot@smart-cactus.org>2020-05-25 09:48:17 -0400
commit013d71204be44d660f01f8eb255db2d48b832421 (patch)
tree21ec9f79ef846bfa120471999b9fc47f7a6a9f17 /libraries/base/GHC/Generics.hs
parentcd339ef0e8ce940902df79ed1d93b3af50ea6f77 (diff)
downloadhaskell-013d71204be44d660f01f8eb255db2d48b832421.tar.gz
Revert "Specify kind variables for inferred kinds in base."
As noted in !3132, this has rather severe knock-on consequences in user-code. We'll need to revisit this before merging something along these lines. This reverts commit 9749fe1223d182b1f8e7e4f7378df661c509f396.
Diffstat (limited to 'libraries/base/GHC/Generics.hs')
-rw-r--r--libraries/base/GHC/Generics.hs93
1 files changed, 23 insertions, 70 deletions
diff --git a/libraries/base/GHC/Generics.hs b/libraries/base/GHC/Generics.hs
index e565d0bfe7..f305e09ea3 100644
--- a/libraries/base/GHC/Generics.hs
+++ b/libraries/base/GHC/Generics.hs
@@ -11,10 +11,8 @@
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE PolyKinds #-}
-{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
-{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
@@ -759,8 +757,7 @@ import GHC.TypeLits ( KnownSymbol, KnownNat, symbolVal, natVal )
--------------------------------------------------------------------------------
-- | Void: used for datatypes without constructors
-type V1 :: forall k. k -> Type
-data V1 a
+data V1 (p :: k)
deriving ( Eq -- ^ @since 4.9.0.0
, Ord -- ^ @since 4.9.0.0
, Read -- ^ @since 4.9.0.0
@@ -775,8 +772,7 @@ instance Semigroup (V1 p) where
v <> _ = v
-- | Unit: used for constructors without arguments
-type U1 :: forall k. k -> Type
-data U1 a = U1
+data U1 (p :: k) = U1
deriving ( Generic -- ^ @since 4.7.0.0
, Generic1 -- ^ @since 4.9.0.0
)
@@ -827,8 +823,7 @@ instance Monoid (U1 p) where
mempty = U1
-- | Used for marking occurrences of the parameter
-type Par1 :: Type -> Type
-newtype Par1 a = Par1 { unPar1 :: a }
+newtype Par1 p = Par1 { unPar1 :: p }
deriving ( Eq -- ^ @since 4.7.0.0
, Ord -- ^ @since 4.7.0.0
, Read -- ^ @since 4.7.0.0
@@ -856,8 +851,7 @@ deriving instance Monoid p => Monoid (Par1 p)
-- | Recursive calls of kind @* -> *@ (or kind @k -> *@, when @PolyKinds@
-- is enabled)
-type Rec1 :: forall k. (k -> Type) -> (k -> Type)
-newtype Rec1 f a = Rec1 { unRec1 :: f a }
+newtype Rec1 (f :: k -> Type) (p :: k) = Rec1 { unRec1 :: f p }
deriving ( Eq -- ^ @since 4.7.0.0
, Ord -- ^ @since 4.7.0.0
, Read -- ^ @since 4.7.0.0
@@ -887,8 +881,7 @@ deriving instance Semigroup (f p) => Semigroup (Rec1 f p)
deriving instance Monoid (f p) => Monoid (Rec1 f p)
-- | Constants, additional parameters and recursion of kind @*@
-type K1 :: forall k. Type -> Type -> k -> Type
-newtype K1 i a b = K1 { unK1 :: a }
+newtype K1 (i :: Type) c (p :: k) = K1 { unK1 :: c }
deriving ( Eq -- ^ @since 4.7.0.0
, Ord -- ^ @since 4.7.0.0
, Read -- ^ @since 4.7.0.0
@@ -929,9 +922,8 @@ deriving instance Semigroup (f p) => Semigroup (M1 i c f p)
deriving instance Monoid (f p) => Monoid (M1 i c f p)
-- | Meta-information (constructor names, etc.)
-type M1 :: forall k. Type -> Meta -> (k -> Type) -> (k -> Type)
-newtype M1 i meta f a =
- M1 { unM1 :: f a }
+newtype M1 (i :: Type) (c :: Meta) (f :: k -> Type) (p :: k) =
+ M1 { unM1 :: f p }
deriving ( Eq -- ^ @since 4.7.0.0
, Ord -- ^ @since 4.7.0.0
, Read -- ^ @since 4.7.0.0
@@ -943,8 +935,7 @@ newtype M1 i meta f a =
-- | Sums: encode choice between constructors
infixr 5 :+:
-type (:+:) :: forall k. (k -> Type) -> (k -> Type) -> (k -> Type)
-data (f :+: g) a = L1 (f a) | R1 (g a)
+data (:+:) (f :: k -> Type) (g :: k -> Type) (p :: k) = L1 (f p) | R1 (g p)
deriving ( Eq -- ^ @since 4.7.0.0
, Ord -- ^ @since 4.7.0.0
, Read -- ^ @since 4.7.0.0
@@ -956,8 +947,7 @@ data (f :+: g) a = L1 (f a) | R1 (g a)
-- | Products: encode multiple arguments to constructors
infixr 6 :*:
-type (:*:) :: forall k. (k -> Type) -> (k -> Type) -> (k -> Type)
-data (f :*: g) a = f a :*: g a
+data (:*:) (f :: k -> Type) (g :: k -> Type) (p :: k) = f p :*: g p
deriving ( Eq -- ^ @since 4.7.0.0
, Ord -- ^ @since 4.7.0.0
, Read -- ^ @since 4.7.0.0
@@ -998,9 +988,8 @@ instance (Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p) where
-- | Composition of functors
infixr 7 :.:
-type (:.:) :: forall k2 k1. (k2 -> Type) -> (k1 -> k2) -> (k1 -> Type)
-newtype (f :.: g) a =
- Comp1 { unComp1 :: f (g a) }
+newtype (:.:) (f :: k2 -> Type) (g :: k1 -> k2) (p :: k1) =
+ Comp1 { unComp1 :: f (g p) }
deriving ( Eq -- ^ @since 4.7.0.0
, Ord -- ^ @since 4.7.0.0
, Read -- ^ @since 4.7.0.0
@@ -1031,7 +1020,6 @@ deriving instance Monoid (f (g p)) => Monoid ((f :.: g) p)
-- | Constants of unlifted kinds
--
-- @since 4.9.0.0
-type URec :: forall k. Type -> k -> Type
data family URec (a :: Type) (p :: k)
-- | Used for marking occurrences of 'Addr#'
@@ -1105,46 +1093,37 @@ data instance URec Word (p :: k) = UWord { uWord# :: Word# }
-- | Type synonym for @'URec' 'Addr#'@
--
--- @since 4.9.0.0. Kind `k` explicitly quantified since 4.15.0.0.
-type UAddr :: forall k. k -> Type
-type UAddr = URec (Ptr ())
+-- @since 4.9.0.0
+type UAddr = URec (Ptr ())
-- | Type synonym for @'URec' 'Char#'@
--
--- @since 4.9.0.0. Kind `k` explicitly quantified since 4.15.0.0.
-type UChar :: forall k. k -> Type
-type UChar = URec Char
+-- @since 4.9.0.0
+type UChar = URec Char
-- | Type synonym for @'URec' 'Double#'@
--
--- @since 4.9.0.0. Kind `k` explicitly quantified since 4.15.0.0.
-type UDouble :: forall k. k -> Type
+-- @since 4.9.0.0
type UDouble = URec Double
-- | Type synonym for @'URec' 'Float#'@
--
--- @since 4.9.0.0. Kind `k` explicitly quantified since 4.15.0.0.
-type UFloat :: forall k. k -> Type
-type UFloat = URec Float
+-- @since 4.9.0.0
+type UFloat = URec Float
-- | Type synonym for @'URec' 'Int#'@
--
--- @since 4.9.0.0. Kind `k` explicitly quantified since 4.15.0.0.
-type UInt :: forall k. k -> Type
-type UInt = URec Int
+-- @since 4.9.0.0
+type UInt = URec Int
-- | Type synonym for @'URec' 'Word#'@
--
--- @since 4.9.0.0. Kind `k` explicitly quantified since 4.15.0.0.
-type UWord :: forall k. k -> Type
-type UWord = URec Word
+-- @since 4.9.0.0
+type UWord = URec Word
-- | Tag for K1: recursion (of kind @Type@)
data R
-- | Type synonym for encoding recursion (of kind @Type@)
---
--- Kind `k` explicitly quantified since 4.15.0.0.
-type Rec0 :: forall k. Type -> k -> Type
type Rec0 = K1 R
-- | Tag for M1: datatype
@@ -1155,27 +1134,15 @@ data C
data S
-- | Type synonym for encoding meta-information for datatypes
---
--- Kind `k` explicitly quantified since 4.15.0.0.
-type D1 :: forall k. Meta -> (k -> Type) -> (k -> Type)
type D1 = M1 D
-- | Type synonym for encoding meta-information for constructors
---
--- Kind `k` explicitly quantified since 4.15.0.0.
-type C1 :: forall k. Meta -> (k -> Type) -> (k -> Type)
type C1 = M1 C
-- | Type synonym for encoding meta-information for record selectors
---
--- Kind `k` explicitly quantified since 4.15.0.0.
-type S1 :: forall k. Meta -> (k -> Type) -> (k -> Type)
type S1 = M1 S
-- | Class for datatypes that represent datatypes
---
--- Kind `k` explicitly quantified since 4.15.0.0.
-type Datatype :: forall k. k -> Constraint
class Datatype d where
-- | The name of the datatype (unqualified)
datatypeName :: t d (f :: k -> Type) (a :: k) -> [Char]
@@ -1200,9 +1167,6 @@ instance (KnownSymbol n, KnownSymbol m, KnownSymbol p, SingI nt)
isNewtype _ = fromSing (sing :: Sing nt)
-- | Class for datatypes that represent data constructors
---
--- Kind `k` explicitly quantified since 4.15.0.0.
-type Constructor :: forall k. k -> Constraint
class Constructor c where
-- | The name of the constructor
conName :: t c (f :: k -> Type) (a :: k) -> [Char]
@@ -1342,9 +1306,6 @@ data DecidedStrictness = DecidedLazy
)
-- | Class for datatypes that represent records
---
--- Kind `k` explicitly quantified since 4.15.0.0.
-type Selector :: forall k. k -> Constraint
class Selector s where
-- | The name of the selector
selName :: t s (f :: k -> Type) (a :: k) -> [Char]
@@ -1397,7 +1358,6 @@ class Generic a where
-- 'from1' . 'to1' ≡ 'Prelude.id'
-- 'to1' . 'from1' ≡ 'Prelude.id'
-- @
-type Generic1 :: forall k. (k -> Type) -> Constraint
class Generic1 (f :: k -> Type) where
-- | Generic representation type
type Rep1 f :: k -> Type
@@ -1530,16 +1490,10 @@ deriving instance Generic1 Down
--------------------------------------------------------------------------------
-- | The singleton kind-indexed data family.
---
--- Kind `k` explicitly quantified since 4.15.0.0.
-type Sing :: forall k. k -> Type
data family Sing (a :: k)
-- | A 'SingI' constraint is essentially an implicitly-passed singleton.
---
--- Kind `k` explicitly quantified since 4.15.0.0.
-type SingI :: forall k. k -> Constraint
-class SingI a where
+class SingI (a :: k) where
-- | Produce the singleton explicitly. You will likely need the @ScopedTypeVariables@
-- extension to use this method the way you want.
sing :: Sing a
@@ -1547,7 +1501,6 @@ class SingI a where
-- | The 'SingKind' class is essentially a /kind/ class. It classifies all kinds
-- for which singletons are defined. The class supports converting between a singleton
-- type and the base (unrefined) type which it is built from.
-type SingKind :: Type -> Constraint
class SingKind k where
-- | Get a base type from a proxy for the promoted kind. For example,
-- @DemoteRep Bool@ will be the type @Bool@.