diff options
Diffstat (limited to 'libraries/base')
-rw-r--r-- | libraries/base/Control/Arrow.hs | 4 | ||||
-rw-r--r-- | libraries/base/Control/Category.hs | 4 | ||||
-rw-r--r-- | libraries/base/Data/Data.hs | 2 | ||||
-rw-r--r-- | libraries/base/Data/Dynamic.hs | 6 | ||||
-rw-r--r-- | libraries/base/Data/Fixed.hs | 15 | ||||
-rw-r--r-- | libraries/base/Data/Functor/Compose.hs | 7 | ||||
-rw-r--r-- | libraries/base/Data/Functor/Const.hs | 5 | ||||
-rw-r--r-- | libraries/base/Data/Functor/Product.hs | 6 | ||||
-rw-r--r-- | libraries/base/Data/Functor/Sum.hs | 6 | ||||
-rw-r--r-- | libraries/base/Data/Type/Coercion.hs | 41 | ||||
-rw-r--r-- | libraries/base/Data/Type/Equality.hs | 34 | ||||
-rw-r--r-- | libraries/base/GHC/Generics.hs | 93 | ||||
-rw-r--r-- | libraries/base/changelog.md | 8 |
13 files changed, 68 insertions, 163 deletions
diff --git a/libraries/base/Control/Arrow.hs b/libraries/base/Control/Arrow.hs index 56fa82e161..eec25a3179 100644 --- a/libraries/base/Control/Arrow.hs +++ b/libraries/base/Control/Arrow.hs @@ -1,8 +1,8 @@ +{-# LANGUAGE Trustworthy #-} +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE DeriveGeneric #-} -{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE StandaloneDeriving #-} -{-# LANGUAGE Trustworthy #-} {-# OPTIONS_GHC -Wno-inline-rule-shadowing #-} -- The RULES for the methods of class Arrow may never fire -- e.g. compose/arr; see #10528 diff --git a/libraries/base/Control/Category.hs b/libraries/base/Control/Category.hs index 14584bdc0c..c033c7618e 100644 --- a/libraries/base/Control/Category.hs +++ b/libraries/base/Control/Category.hs @@ -1,7 +1,7 @@ +{-# LANGUAGE Trustworthy #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE PolyKinds #-} -{-# LANGUAGE Trustworthy #-} {-# OPTIONS_GHC -Wno-inline-rule-shadowing #-} -- The RULES for the methods of class Category may never fire -- e.g. identity/left, identity/right, association; see #10528 @@ -20,7 +20,7 @@ module Control.Category where -import qualified GHC.Base (id, (.)) +import qualified GHC.Base (id,(.)) import Data.Type.Coercion import Data.Type.Equality import Data.Coerce (coerce) diff --git a/libraries/base/Data/Data.hs b/libraries/base/Data/Data.hs index 0ce830742a..a8dfa61115 100644 --- a/libraries/base/Data/Data.hs +++ b/libraries/base/Data/Data.hs @@ -1,10 +1,10 @@ {-# LANGUAGE BangPatterns #-} -{-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE DataKinds #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} diff --git a/libraries/base/Data/Dynamic.hs b/libraries/base/Data/Dynamic.hs index 8478f0e680..5a4f3f9a08 100644 --- a/libraries/base/Data/Dynamic.hs +++ b/libraries/base/Data/Dynamic.hs @@ -1,9 +1,9 @@ -{-# LANGUAGE ExplicitForAll #-} -{-# LANGUAGE GADTs #-} +{-# LANGUAGE Trustworthy #-} {-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE ExplicitForAll #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE Trustworthy #-} {-# LANGUAGE TypeApplications #-} ----------------------------------------------------------------------------- diff --git a/libraries/base/Data/Fixed.hs b/libraries/base/Data/Fixed.hs index 17e5141b33..232175a1ab 100644 --- a/libraries/base/Data/Fixed.hs +++ b/libraries/base/Data/Fixed.hs @@ -1,9 +1,7 @@ -{-# LANGUAGE FlexibleInstances #-} -{-# LANGUAGE PolyKinds #-} -{-# LANGUAGE RankNTypes #-} -{-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE StandaloneKindSignatures #-} {-# LANGUAGE Trustworthy #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE FlexibleInstances #-} ----------------------------------------------------------------------------- -- | @@ -43,7 +41,6 @@ module Data.Fixed import Data.Data import GHC.TypeLits (KnownNat, natVal) import GHC.Read -import Data.Kind (Type, Constraint) import Text.ParserCombinators.ReadPrec import Text.Read.Lex @@ -64,8 +61,7 @@ mod' n d = n - (fromInteger f) * d where f = div' n d -- | The type parameter should be an instance of 'HasResolution'. -type Fixed :: forall k. k -> Type -newtype Fixed a = MkFixed Integer +newtype Fixed (a :: k) = MkFixed Integer deriving ( Eq -- ^ @since 2.01 , Ord -- ^ @since 2.01 ) @@ -84,8 +80,7 @@ instance (Typeable k,Typeable a) => Data (Fixed (a :: k)) where dataTypeOf _ = tyFixed toConstr _ = conMkFixed -type HasResolution :: forall k. k -> Constraint -class HasResolution a where +class HasResolution (a :: k) where resolution :: p a -> Integer -- | For example, @Fixed 1000@ will give you a 'Fixed' with a resolution of 1000. diff --git a/libraries/base/Data/Functor/Compose.hs b/libraries/base/Data/Functor/Compose.hs index 225d16283b..d8369ebc05 100644 --- a/libraries/base/Data/Functor/Compose.hs +++ b/libraries/base/Data/Functor/Compose.hs @@ -3,7 +3,6 @@ {-# LANGUAGE GADTs #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE StandaloneKindSignatures #-} {-# LANGUAGE Trustworthy #-} {-# LANGUAGE TypeOperators #-} ----------------------------------------------------------------------------- @@ -27,7 +26,6 @@ module Data.Functor.Compose ( import Data.Functor.Classes -import Data.Kind (Type) import Control.Applicative import Data.Coerce (coerce) import Data.Data (Data) @@ -40,9 +38,6 @@ infixr 9 `Compose` -- | Right-to-left composition of functors. -- The composition of applicative functors is always applicative, -- but the composition of monads is not always a monad. --- --- Kinds `k2` and `k1` explicitly quantified since 4.15.0.0. -type Compose :: forall k2 k1. (k2 -> Type) -> (k1 -> k2) -> (k1 -> Type) newtype Compose f g a = Compose { getCompose :: f (g a) } deriving ( Data -- ^ @since 4.9.0.0 , Generic -- ^ @since 4.9.0.0 @@ -131,7 +126,7 @@ instance (Alternative f, Applicative g) => Alternative (Compose f g) where -- | The deduction (via generativity) that if @g x :~: g y@ then @x :~: y@. -- -- @since 4.14.0.0 -instance TestEquality f => TestEquality (Compose f g) where +instance (TestEquality f) => TestEquality (Compose f g) where testEquality (Compose x) (Compose y) = case testEquality x y of -- :: Maybe (g x :~: g y) Just Refl -> Just Refl -- :: Maybe (x :~: y) diff --git a/libraries/base/Data/Functor/Const.hs b/libraries/base/Data/Functor/Const.hs index dd1880e30b..651041f15b 100644 --- a/libraries/base/Data/Functor/Const.hs +++ b/libraries/base/Data/Functor/Const.hs @@ -2,9 +2,7 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE PolyKinds #-} -{-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE StandaloneKindSignatures #-} {-# LANGUAGE Trustworthy #-} ----------------------------------------------------------------------------- @@ -38,9 +36,6 @@ import GHC.Read (Read(readsPrec), readParen, lex) import GHC.Show (Show(showsPrec), showParen, showString) -- | The 'Const' functor. --- --- Kind `k` explicitly quantified since 4.15.0.0. -type Const :: forall k. Type -> k -> Type newtype Const a b = Const { getConst :: a } deriving ( Bits -- ^ @since 4.9.0.0 , Bounded -- ^ @since 4.9.0.0 diff --git a/libraries/base/Data/Functor/Product.hs b/libraries/base/Data/Functor/Product.hs index 266a72d75e..a3678e910e 100644 --- a/libraries/base/Data/Functor/Product.hs +++ b/libraries/base/Data/Functor/Product.hs @@ -1,9 +1,7 @@ {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE PolyKinds #-} -{-# LANGUAGE RankNTypes #-} {-# LANGUAGE Safe #-} -{-# LANGUAGE StandaloneKindSignatures #-} ----------------------------------------------------------------------------- -- | -- Module : Data.Functor.Product @@ -28,15 +26,11 @@ import Control.Monad (MonadPlus(..)) import Control.Monad.Fix (MonadFix(..)) import Control.Monad.Zip (MonadZip(mzipWith)) import Data.Data (Data) -import Data.Kind (Type) import Data.Functor.Classes import GHC.Generics (Generic, Generic1) import Text.Read (Read(..), readListDefault, readListPrecDefault) -- | Lifted product of functors. --- --- Kind `k` explicitly quantified since 4.15.0.0. -type Product :: forall k. (k -> Type) -> (k -> Type) -> (k -> Type) data Product f g a = Pair (f a) (g a) deriving ( Data -- ^ @since 4.9.0.0 , Generic -- ^ @since 4.9.0.0 diff --git a/libraries/base/Data/Functor/Sum.hs b/libraries/base/Data/Functor/Sum.hs index cca541fe5e..f7d6178a2b 100644 --- a/libraries/base/Data/Functor/Sum.hs +++ b/libraries/base/Data/Functor/Sum.hs @@ -1,9 +1,7 @@ {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE PolyKinds #-} -{-# LANGUAGE RankNTypes #-} {-# LANGUAGE Safe #-} -{-# LANGUAGE StandaloneKindSignatures #-} ----------------------------------------------------------------------------- -- | -- Module : Data.Functor.Sum @@ -25,15 +23,11 @@ module Data.Functor.Sum ( import Control.Applicative ((<|>)) import Data.Data (Data) -import Data.Kind (Type) import Data.Functor.Classes import GHC.Generics (Generic, Generic1) import Text.Read (Read(..), readListDefault, readListPrecDefault) -- | Lifted sum of functors. --- --- Kind `k` explicitly quantified since 4.15.0.0. -type Sum :: forall k. (k -> Type) -> (k -> Type) -> (k -> Type) data Sum f g a = InL (f a) | InR (g a) deriving ( Data -- ^ @since 4.9.0.0 , Generic -- ^ @since 4.9.0.0 diff --git a/libraries/base/Data/Type/Coercion.hs b/libraries/base/Data/Type/Coercion.hs index a3c920d8e4..694bedec01 100644 --- a/libraries/base/Data/Type/Coercion.hs +++ b/libraries/base/Data/Type/Coercion.hs @@ -1,16 +1,14 @@ -{-# LANGUAGE DeriveGeneric #-} -{-# LANGUAGE FlexibleInstances #-} -{-# LANGUAGE GADTs #-} -{-# LANGUAGE MagicHash #-} -{-# LANGUAGE NoImplicitPrelude #-} -{-# LANGUAGE PolyKinds #-} -{-# LANGUAGE RankNTypes #-} -{-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE StandaloneDeriving #-} -{-# LANGUAGE StandaloneKindSignatures #-} -{-# LANGUAGE TypeApplications #-} -{-# LANGUAGE TypeFamilies #-} -{-# LANGUAGE TypeOperators #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE TypeOperators #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE MagicHash #-} ----------------------------------------------------------------------------- -- | @@ -49,10 +47,9 @@ import GHC.Base -- To use this equality in practice, pattern-match on the @Coercion a b@ to get out -- the @Coercible a b@ instance, and then use 'coerce' to apply it. -- --- @since 4.7.0.0. Kind `k` explicitly quantified since 4.15.0.0. -type Coercion :: forall k. k -> k -> Type +-- @since 4.7.0.0 data Coercion a b where - Coercion :: Coercible @k a b => Coercion @k a b + Coercion :: Coercible a b => Coercion a b -- with credit to Conal Elliott for 'ty', Erik Hesselink & Martijn van -- Steenbergen for 'type-equality', Edward Kmett for 'eq', and Gabor Greif @@ -81,13 +78,13 @@ repr :: (a Eq.:~: b) -> Coercion a b repr Eq.Refl = Coercion -- | @since 4.7.0.0 -deriving instance Eq (Coercion a b) +deriving instance Eq (Coercion a b) -- | @since 4.7.0.0 deriving instance Show (Coercion a b) -- | @since 4.7.0.0 -deriving instance Ord (Coercion a b) +deriving instance Ord (Coercion a b) -- | @since 4.7.0.0 deriving instance Coercible a b => Read (Coercion a b) @@ -105,13 +102,9 @@ deriving instance Coercible a b => Bounded (Coercion a b) -- | This class contains types where you can learn the equality of two types -- from information contained in /terms/. Typically, only singleton types should -- inhabit this class. --- --- Kind `k` explicitly quantified since 4.15.0.0. -type TestCoercion :: forall k. (k -> Type) -> Constraint -class TestCoercion (f :: k -> Type) where +class TestCoercion f where -- | Conditionally prove the representational equality of @a@ and @b@. - testCoercion :: forall (a :: k) (b :: k). - f a -> f b -> Maybe (Coercion @k a b) + testCoercion :: f a -> f b -> Maybe (Coercion a b) -- | @since 4.7.0.0 instance TestCoercion ((Eq.:~:) a) where diff --git a/libraries/base/Data/Type/Equality.hs b/libraries/base/Data/Type/Equality.hs index aa19ae3064..ab321ba011 100644 --- a/libraries/base/Data/Type/Equality.hs +++ b/libraries/base/Data/Type/Equality.hs @@ -1,20 +1,19 @@ -{-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveGeneric #-} -{-# LANGUAGE ExplicitNamespaces #-} -{-# LANGUAGE FlexibleInstances #-} -{-# LANGUAGE FunctionalDependencies #-} +{-# LANGUAGE TypeOperators #-} {-# LANGUAGE GADTs #-} -{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE NoImplicitPrelude #-} -{-# LANGUAGE PolyKinds #-} {-# LANGUAGE RankNTypes #-} -{-# LANGUAGE StandaloneDeriving #-} -{-# LANGUAGE StandaloneKindSignatures #-} -{-# LANGUAGE Trustworthy #-} -{-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeFamilies #-} -{-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE ExplicitNamespaces #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE FunctionalDependencies #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE StandaloneKindSignatures #-} +{-# LANGUAGE Trustworthy #-} ----------------------------------------------------------------------------- -- | @@ -62,8 +61,7 @@ infix 4 :~:, :~~: -- in practice, pattern-match on the @a :~: b@ to get out the @Refl@ constructor; -- in the body of the pattern-match, the compiler knows that @a ~ b@. -- --- @since 4.7.0.0. Kind `k` explicitly quantified since 4.15.0.0. -type (:~:) :: forall k. k -> k -> Type +-- @since 4.7.0.0 data a :~: b where -- See Note [The equality types story] in GHC.Builtin.Types.Prim Refl :: a :~: a @@ -124,9 +122,8 @@ deriving instance a ~ b => Bounded (a :~: b) -- | Kind heterogeneous propositional equality. Like ':~:', @a :~~: b@ is -- inhabited by a terminating value if and only if @a@ is the same type as @b@. -- --- @since 4.10.0.0. Kinds `k1` and `k2` explicitly quantified since --- 4.15.0.0. -type (:~~:) :: forall k1 k2. k1 -> k2 -> Type +-- @since 4.10.0.0 +type (:~~:) :: k1 -> k2 -> Type data a :~~: b where HRefl :: a :~~: a @@ -153,9 +150,6 @@ deriving instance a ~~ b => Bounded (a :~~: b) -- | This class contains types where you can learn the equality of two types -- from information contained in /terms/. Typically, only singleton types should -- inhabit this class. --- --- Kind `k` explicitly quantified since 4.15.0.0. -type TestEquality :: forall k. (k -> Type) -> Constraint class TestEquality f where -- | Conditionally prove the equality of @a@ and @b@. testEquality :: f a -> f b -> Maybe (a :~: b) @@ -171,7 +165,7 @@ instance TestEquality ((:~~:) a) where infix 4 == -- | A type family to compute Boolean equality. -type (==) :: forall k. k -> k -> Bool +type (==) :: k -> k -> Bool type family a == b where f a == g b = f == g && a == b a == a = 'True 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@. diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 52d6a100de..06b9a108ef 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -2,14 +2,6 @@ ## 4.15.0.0 *TBA* - * `Const` (`Data.Functor.Const`), `Compose` (`Data.Functor.Compose`), - `Product` (`Data.Functor.Product`), `Sum` (`Data.Functor.Sum`), `Coercion` - and `TestCoercion` (`Data.Type.Coercion`), `(:~:)` and `TestEquality` - (`Data.Type.Equality`); `UAddr`, `UChar`, `UDouble` `UFloat`, `UInt`, - `UWord`, `Rec0`, `D1`, `C1`, `S1`, `Datatype`, `Constructor`, `Selector` - (`GHC.Generics`) now use specified quantification, allowing the use of - visible kind application. - * `openFile` now calls the `open` system call with an `interruptible` FFI call, ensuring that the call can be interrupted with `SIGINT` on POSIX systems. |