summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorVladislav Zavialov <vlad.z.4096@gmail.com>2019-09-28 15:20:39 +0300
committerVladislav Zavialov <vlad.z.4096@gmail.com>2019-09-28 15:20:39 +0300
commit39003e3e56c04916da97180224ab6a20b7c20870 (patch)
tree800f977ab90b6dfe29ff5628b366936636b1cc3e
parent6f9fa0be8d43a7c9618f6e27e3190dc08bf86bfa (diff)
downloadhaskell-wip/libraries-no-cusks.tar.gz
Do not rely on CUSKs in 'base'wip/libraries-no-cusks
Use standalone kind signatures instead of complete user-specified kinds in Data.Type.Equality and Data.Typeable
-rw-r--r--libraries/base/Data/Type/Equality.hs7
-rw-r--r--libraries/base/Data/Typeable/Internal.hs4
2 files changed, 8 insertions, 3 deletions
diff --git a/libraries/base/Data/Type/Equality.hs b/libraries/base/Data/Type/Equality.hs
index f9c9cc23da..e900546671 100644
--- a/libraries/base/Data/Type/Equality.hs
+++ b/libraries/base/Data/Type/Equality.hs
@@ -12,6 +12,7 @@
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE Trustworthy #-}
-----------------------------------------------------------------------------
@@ -122,7 +123,8 @@ deriving instance a ~ b => Bounded (a :~: b)
-- inhabited by a terminating value if and only if @a@ is the same type as @b@.
--
-- @since 4.10.0.0
-data (a :: k1) :~~: (b :: k2) where
+type (:~~:) :: k1 -> k2 -> Type
+data a :~~: b where
HRefl :: a :~~: a
-- | @since 4.10.0.0
@@ -163,7 +165,8 @@ instance TestEquality ((:~~:) a) where
infix 4 ==
-- | A type family to compute Boolean equality.
-type family (a :: k) == (b :: k) :: Bool where
+type (==) :: k -> k -> Bool
+type family a == b where
f a == g b = f == g && a == b
a == a = 'True
_ == _ = 'False
diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs
index 5c087272fa..6135487e6e 100644
--- a/libraries/base/Data/Typeable/Internal.hs
+++ b/libraries/base/Data/Typeable/Internal.hs
@@ -18,6 +18,7 @@
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE StandaloneKindSignatures #-}
-----------------------------------------------------------------------------
-- |
@@ -178,7 +179,8 @@ rnfTyCon (TyCon _ _ m n _ k) = rnfModule m `seq` rnfTrName n `seq` rnfKindRep k
-- | A concrete representation of a (monomorphic) type.
-- 'TypeRep' supports reasonably efficient equality.
-data TypeRep (a :: k) where
+type TypeRep :: k -> Type
+data TypeRep a where
-- The TypeRep of Type. See Note [Kind caching], Wrinkle 2
TrType :: TypeRep Type
TrTyCon :: { -- See Note [TypeRep fingerprints]