diff options
Diffstat (limited to 'libraries')
-rw-r--r-- | libraries/base/Data/Data.hs | 4 | ||||
-rw-r--r-- | libraries/base/Data/Kind.hs | 2 | ||||
-rw-r--r-- | libraries/base/Data/Proxy.hs | 2 | ||||
-rw-r--r-- | libraries/base/Data/Type/Equality.hs | 4 | ||||
-rw-r--r-- | libraries/base/Data/Typeable.hs | 26 | ||||
-rw-r--r-- | libraries/base/Data/Typeable/Internal.hs | 1 | ||||
-rw-r--r-- | libraries/base/GHC/Base.hs | 3 | ||||
-rw-r--r-- | libraries/base/GHC/Err.hs | 2 | ||||
-rw-r--r-- | libraries/base/GHC/Generics.hs | 50 | ||||
-rw-r--r-- | libraries/base/Type/Reflection/Unsafe.hs | 2 | ||||
-rw-r--r-- | libraries/base/tests/CatEntail.hs | 4 | ||||
-rw-r--r-- | libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs | 1 | ||||
-rw-r--r-- | libraries/ghc-prim/GHC/Magic.hs | 3 | ||||
-rw-r--r-- | libraries/ghc-prim/GHC/Types.hs | 8 |
14 files changed, 55 insertions, 57 deletions
diff --git a/libraries/base/Data/Data.hs b/libraries/base/Data/Data.hs index 6d214907e4..8154433044 100644 --- a/libraries/base/Data/Data.hs +++ b/libraries/base/Data/Data.hs @@ -4,12 +4,12 @@ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE DataKinds #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE Trustworthy #-} -{-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} ----------------------------------------------------------------------------- @@ -1310,7 +1310,7 @@ deriving instance (Typeable f, Typeable g, Data p, Data (f p), Data (g p)) => Data ((f :+: g) p) -- | @since 4.9.0.0 -deriving instance (Typeable (f :: * -> *), Typeable (g :: * -> *), +deriving instance (Typeable (f :: Type -> Type), Typeable (g :: Type -> Type), Data p, Data (f (g p))) => Data ((f :.: g) p) diff --git a/libraries/base/Data/Kind.hs b/libraries/base/Data/Kind.hs index 348301347c..9ee7b7ab07 100644 --- a/libraries/base/Data/Kind.hs +++ b/libraries/base/Data/Kind.hs @@ -14,6 +14,6 @@ -- @since 4.9.0.0 ----------------------------------------------------------------------------- -module Data.Kind ( Type, Constraint, type (*), type (★) ) where +module Data.Kind ( Type, Constraint ) where import GHC.Types diff --git a/libraries/base/Data/Proxy.hs b/libraries/base/Data/Proxy.hs index cdbb0d4956..557cc1e4dd 100644 --- a/libraries/base/Data/Proxy.hs +++ b/libraries/base/Data/Proxy.hs @@ -59,7 +59,7 @@ data Proxy t = Proxy deriving ( Bounded -- ^ @since 4.7.0.0 -- | A concrete, promotable proxy type, for use at the kind level -- There are no instances for this because it is intended at the kind level only -data KProxy (t :: *) = KProxy +data KProxy (t :: Type) = KProxy -- It's common to use (undefined :: Proxy t) and (Proxy :: Proxy t) -- interchangeably, so all of these instances are hand-written to be diff --git a/libraries/base/Data/Type/Equality.hs b/libraries/base/Data/Type/Equality.hs index 8591499197..50b96c08c1 100644 --- a/libraries/base/Data/Type/Equality.hs +++ b/libraries/base/Data/Type/Equality.hs @@ -5,13 +5,13 @@ {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE RankNTypes #-} -{-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE ExplicitNamespaces #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} -{-# LANGUAGE TypeInType #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE PolyKinds #-} {-# LANGUAGE Trustworthy #-} ----------------------------------------------------------------------------- diff --git a/libraries/base/Data/Typeable.hs b/libraries/base/Data/Typeable.hs index 61b70cfd2e..c9a8711d79 100644 --- a/libraries/base/Data/Typeable.hs +++ b/libraries/base/Data/Typeable.hs @@ -198,28 +198,30 @@ rnfTypeRep = I.rnfSomeTypeRep -- Keeping backwards-compatibility -typeOf1 :: forall t (a :: *). Typeable t => t a -> TypeRep +typeOf1 :: forall t (a :: Type). Typeable t => t a -> TypeRep typeOf1 _ = I.someTypeRep (Proxy :: Proxy t) -typeOf2 :: forall t (a :: *) (b :: *). Typeable t => t a b -> TypeRep +typeOf2 :: forall t (a :: Type) (b :: Type). Typeable t => t a b -> TypeRep typeOf2 _ = I.someTypeRep (Proxy :: Proxy t) -typeOf3 :: forall t (a :: *) (b :: *) (c :: *). Typeable t - => t a b c -> TypeRep +typeOf3 :: forall t (a :: Type) (b :: Type) (c :: Type). + Typeable t => t a b c -> TypeRep typeOf3 _ = I.someTypeRep (Proxy :: Proxy t) -typeOf4 :: forall t (a :: *) (b :: *) (c :: *) (d :: *). Typeable t - => t a b c d -> TypeRep +typeOf4 :: forall t (a :: Type) (b :: Type) (c :: Type) (d :: Type). + Typeable t => t a b c d -> TypeRep typeOf4 _ = I.someTypeRep (Proxy :: Proxy t) -typeOf5 :: forall t (a :: *) (b :: *) (c :: *) (d :: *) (e :: *). Typeable t - => t a b c d e -> TypeRep +typeOf5 :: forall t (a :: Type) (b :: Type) (c :: Type) (d :: Type) (e :: Type). + Typeable t => t a b c d e -> TypeRep typeOf5 _ = I.someTypeRep (Proxy :: Proxy t) -typeOf6 :: forall t (a :: *) (b :: *) (c :: *) (d :: *) (e :: *) (f :: *). - Typeable t => t a b c d e f -> TypeRep +typeOf6 :: forall t (a :: Type) (b :: Type) (c :: Type) + (d :: Type) (e :: Type) (f :: Type). + Typeable t => t a b c d e f -> TypeRep typeOf6 _ = I.someTypeRep (Proxy :: Proxy t) -typeOf7 :: forall t (a :: *) (b :: *) (c :: *) (d :: *) (e :: *) (f :: *) - (g :: *). Typeable t => t a b c d e f g -> TypeRep +typeOf7 :: forall t (a :: Type) (b :: Type) (c :: Type) + (d :: Type) (e :: Type) (f :: Type) (g :: Type). + Typeable t => t a b c d e f g -> TypeRep typeOf7 _ = I.someTypeRep (Proxy :: Proxy t) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index 3b7753de46..09290485e4 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -1,6 +1,5 @@ {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE Trustworthy #-} -{-# LANGUAGE TypeInType #-} {-# LANGUAGE ViewPatterns #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE BangPatterns #-} diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs index bccdab4221..b8f984c440 100644 --- a/libraries/base/GHC/Base.hs +++ b/libraries/base/GHC/Base.hs @@ -84,7 +84,8 @@ Other Prelude modules are much easier with fewer complex dependencies. , ExistentialQuantification , RankNTypes , KindSignatures - , TypeInType + , PolyKinds + , DataKinds #-} -- -Wno-orphans is needed for things like: -- Orphan rule: "x# -# x#" ALWAYS forall x# :: Int# -# x# x# = 0 diff --git a/libraries/base/GHC/Err.hs b/libraries/base/GHC/Err.hs index 3d64c95205..a48fb10a86 100644 --- a/libraries/base/GHC/Err.hs +++ b/libraries/base/GHC/Err.hs @@ -1,6 +1,6 @@ {-# LANGUAGE Trustworthy #-} {-# LANGUAGE NoImplicitPrelude, MagicHash, ImplicitParams #-} -{-# LANGUAGE RankNTypes, TypeInType #-} +{-# LANGUAGE RankNTypes, PolyKinds, DataKinds #-} {-# OPTIONS_HADDOCK hide #-} ----------------------------------------------------------------------------- diff --git a/libraries/base/GHC/Generics.hs b/libraries/base/GHC/Generics.hs index 9ac05286ab..05a96b98eb 100644 --- a/libraries/base/GHC/Generics.hs +++ b/libraries/base/GHC/Generics.hs @@ -15,7 +15,6 @@ {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE Trustworthy #-} {-# LANGUAGE TypeFamilies #-} -{-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE UndecidableInstances #-} @@ -850,7 +849,7 @@ deriving instance Monoid p => Monoid (Par1 p) -- | Recursive calls of kind @* -> *@ (or kind @k -> *@, when @PolyKinds@ -- is enabled) -newtype Rec1 (f :: k -> *) (p :: k) = Rec1 { unRec1 :: f p } +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 @@ -880,7 +879,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 @*@ -newtype K1 (i :: *) c (p :: k) = K1 { unK1 :: c } +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 @@ -921,7 +920,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.) -newtype M1 (i :: *) (c :: Meta) (f :: k -> *) (p :: k) = M1 { unM1 :: f p } +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 @@ -933,7 +933,7 @@ newtype M1 (i :: *) (c :: Meta) (f :: k -> *) (p :: k) = M1 { unM1 :: f p } -- | Sums: encode choice between constructors infixr 5 :+: -data (:+:) (f :: k -> *) (g :: k -> *) (p :: k) = L1 (f p) | R1 (g p) +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 @@ -945,7 +945,7 @@ data (:+:) (f :: k -> *) (g :: k -> *) (p :: k) = L1 (f p) | R1 (g p) -- | Products: encode multiple arguments to constructors infixr 6 :*: -data (:*:) (f :: k -> *) (g :: k -> *) (p :: k) = f p :*: g p +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 @@ -986,7 +986,7 @@ instance (Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p) where -- | Composition of functors infixr 7 :.: -newtype (:.:) (f :: k2 -> *) (g :: k1 -> k2) (p :: k1) = +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 @@ -1018,7 +1018,7 @@ deriving instance Monoid (f (g p)) => Monoid ((f :.: g) p) -- | Constants of unlifted kinds -- -- @since 4.9.0.0 -data family URec (a :: *) (p :: k) +data family URec (a :: Type) (p :: k) -- | Used for marking occurrences of 'Addr#' -- @@ -1118,10 +1118,10 @@ type UInt = URec Int -- @since 4.9.0.0 type UWord = URec Word --- | Tag for K1: recursion (of kind @*@) +-- | Tag for K1: recursion (of kind @Type@) data R --- | Type synonym for encoding recursion (of kind @*@) +-- | Type synonym for encoding recursion (of kind @Type@) type Rec0 = K1 R -- | Tag for M1: datatype @@ -1143,17 +1143,17 @@ type S1 = M1 S -- | Class for datatypes that represent datatypes class Datatype d where -- | The name of the datatype (unqualified) - datatypeName :: t d (f :: k -> *) (a :: k) -> [Char] + datatypeName :: t d (f :: k -> Type) (a :: k) -> [Char] -- | The fully-qualified name of the module where the type is declared - moduleName :: t d (f :: k -> *) (a :: k) -> [Char] + moduleName :: t d (f :: k -> Type) (a :: k) -> [Char] -- | The package name of the module where the type is declared -- -- @since 4.9.0.0 - packageName :: t d (f :: k -> *) (a :: k) -> [Char] + packageName :: t d (f :: k -> Type) (a :: k) -> [Char] -- | Marks if the datatype is actually a newtype -- -- @since 4.7.0.0 - isNewtype :: t d (f :: k -> *) (a :: k) -> Bool + isNewtype :: t d (f :: k -> Type) (a :: k) -> Bool isNewtype _ = False -- | @since 4.9.0.0 @@ -1167,14 +1167,14 @@ instance (KnownSymbol n, KnownSymbol m, KnownSymbol p, SingI nt) -- | Class for datatypes that represent data constructors class Constructor c where -- | The name of the constructor - conName :: t c (f :: k -> *) (a :: k) -> [Char] + conName :: t c (f :: k -> Type) (a :: k) -> [Char] -- | The fixity of the constructor - conFixity :: t c (f :: k -> *) (a :: k) -> Fixity + conFixity :: t c (f :: k -> Type) (a :: k) -> Fixity conFixity _ = Prefix -- | Marks if this constructor is a record - conIsRecord :: t c (f :: k -> *) (a :: k) -> Bool + conIsRecord :: t c (f :: k -> Type) (a :: k) -> Bool conIsRecord _ = False -- | @since 4.9.0.0 @@ -1306,19 +1306,19 @@ data DecidedStrictness = DecidedLazy -- | Class for datatypes that represent records class Selector s where -- | The name of the selector - selName :: t s (f :: k -> *) (a :: k) -> [Char] + selName :: t s (f :: k -> Type) (a :: k) -> [Char] -- | The selector's unpackedness annotation (if any) -- -- @since 4.9.0.0 - selSourceUnpackedness :: t s (f :: k -> *) (a :: k) -> SourceUnpackedness + selSourceUnpackedness :: t s (f :: k -> Type) (a :: k) -> SourceUnpackedness -- | The selector's strictness annotation (if any) -- -- @since 4.9.0.0 - selSourceStrictness :: t s (f :: k -> *) (a :: k) -> SourceStrictness + selSourceStrictness :: t s (f :: k -> Type) (a :: k) -> SourceStrictness -- | The strictness that the compiler inferred for the selector -- -- @since 4.9.0.0 - selDecidedStrictness :: t s (f :: k -> *) (a :: k) -> DecidedStrictness + selDecidedStrictness :: t s (f :: k -> Type) (a :: k) -> DecidedStrictness -- | @since 4.9.0.0 instance (SingI mn, SingI su, SingI ss, SingI ds) @@ -1339,7 +1339,7 @@ instance (SingI mn, SingI su, SingI ss, SingI ds) -- @ class Generic a where -- | Generic representation type - type Rep a :: * -> * + type Rep a :: Type -> Type -- | Convert from the datatype to its representation from :: a -> (Rep a) x -- | Convert from the representation to the datatype @@ -1356,9 +1356,9 @@ class Generic a where -- 'from1' . 'to1' ≡ 'id' -- 'to1' . 'from1' ≡ 'id' -- @ -class Generic1 (f :: k -> *) where +class Generic1 (f :: k -> Type) where -- | Generic representation type - type Rep1 f :: k -> * + type Rep1 f :: k -> Type -- | Convert from the datatype to its representation from1 :: f a -> (Rep1 f) a -- | Convert from the representation to the datatype @@ -1490,7 +1490,7 @@ class SingI (a :: k) where class SingKind k where -- | Get a base type from a proxy for the promoted kind. For example, -- @DemoteRep Bool@ will be the type @Bool@. - type DemoteRep k :: * + type DemoteRep k :: Type -- | Convert a singleton to its unrefined version. fromSing :: Sing (a :: k) -> DemoteRep k diff --git a/libraries/base/Type/Reflection/Unsafe.hs b/libraries/base/Type/Reflection/Unsafe.hs index 9a8af16f36..a109400412 100644 --- a/libraries/base/Type/Reflection/Unsafe.hs +++ b/libraries/base/Type/Reflection/Unsafe.hs @@ -12,7 +12,7 @@ -- type representations. -- ----------------------------------------------------------------------------- -{-# LANGUAGE TypeInType, ScopedTypeVariables #-} +{-# LANGUAGE PolyKinds, DataKinds, ScopedTypeVariables #-} module Type.Reflection.Unsafe ( -- * Type representations diff --git a/libraries/base/tests/CatEntail.hs b/libraries/base/tests/CatEntail.hs index c980a2db73..30023ad5b8 100644 --- a/libraries/base/tests/CatEntail.hs +++ b/libraries/base/tests/CatEntail.hs @@ -2,11 +2,11 @@ {-# LANGUAGE TypeOperators, KindSignatures #-} module CatEntail where import Prelude hiding (id, (.)) -import GHC.Exts (Constraint) +import Data.Kind import Control.Category -- One dictionary to rule them all. -data Dict :: Constraint -> * where +data Dict :: Constraint -> Type where Dict :: ctx => Dict ctx -- Entailment. diff --git a/libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs b/libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs index 518491783f..c01ea32fa8 100644 --- a/libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs +++ b/libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs @@ -137,4 +137,5 @@ data Extension | EmptyDataDeriving | NumericUnderscores | QuantifiedConstraints + | StarIsType deriving (Eq, Enum, Show, Generic) diff --git a/libraries/ghc-prim/GHC/Magic.hs b/libraries/ghc-prim/GHC/Magic.hs index 7d6f60e411..ae95bfcbf4 100644 --- a/libraries/ghc-prim/GHC/Magic.hs +++ b/libraries/ghc-prim/GHC/Magic.hs @@ -3,7 +3,8 @@ {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} -{-# LANGUAGE TypeInType #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE PolyKinds #-} {-# LANGUAGE ScopedTypeVariables #-} ----------------------------------------------------------------------------- diff --git a/libraries/ghc-prim/GHC/Types.hs b/libraries/ghc-prim/GHC/Types.hs index ce526b454d..26c92cec83 100644 --- a/libraries/ghc-prim/GHC/Types.hs +++ b/libraries/ghc-prim/GHC/Types.hs @@ -32,7 +32,7 @@ module GHC.Types ( Nat, Symbol, Any, type (~~), Coercible, - TYPE, RuntimeRep(..), Type, type (*), type (★), Constraint, + TYPE, RuntimeRep(..), Type, Constraint, -- The historical type * should ideally be written as -- `type *`, without the parentheses. But that's a true -- pain to parse, and for little gain. @@ -59,12 +59,6 @@ data Constraint -- | The kind of types with values. For example @Int :: Type@. type Type = TYPE 'LiftedRep --- | A backward-compatible (pre-GHC 8.0) synonym for 'Type' -type * = TYPE 'LiftedRep - --- | A unicode backward-compatible (pre-GHC 8.0) synonym for 'Type' -type ★ = TYPE 'LiftedRep - {- ********************************************************************* * * Nat and Symbol |