summaryrefslogtreecommitdiff
path: root/libraries
diff options
context:
space:
mode:
authorsheaf <sam.derbyshire@gmail.com>2021-06-09 20:43:42 +0200
committerMarge Bot <ben+marge-bot@smart-cactus.org>2021-06-10 13:54:05 -0400
commit472c2bf003e9f3bb93b82265f2a0a7124f944421 (patch)
tree74767fe0b48521254b22350d4b1f34a3957adc06 /libraries
parent61c51c00b6e12e309bc5643e89330b93d86f5449 (diff)
downloadhaskell-472c2bf003e9f3bb93b82265f2a0a7124f944421.tar.gz
Reword: representation instead of levity
fixes #19756, updates haddock submodule
Diffstat (limited to 'libraries')
-rw-r--r--libraries/base/GHC/Base.hs2
-rw-r--r--libraries/base/GHC/Conc/Sync.hs2
-rw-r--r--libraries/base/Unsafe/Coerce.hs6
-rw-r--r--libraries/ghc-prim/GHC/Magic.hs4
-rw-r--r--libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs2
-rw-r--r--libraries/template-haskell/Language/Haskell/TH/Syntax.hs8
6 files changed, 12 insertions, 12 deletions
diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs
index 5eb0da3ea1..b037951fa8 100644
--- a/libraries/base/GHC/Base.hs
+++ b/libraries/base/GHC/Base.hs
@@ -1514,7 +1514,7 @@ flip f x y = f y x
-- It is also useful in higher-order situations, such as @'map' ('$' 0) xs@,
-- or @'Data.List.zipWith' ('$') fs xs@.
--
--- Note that @('$')@ is levity-polymorphic in its result type, so that
+-- Note that @('$')@ is representation-polymorphic in its result type, so that
-- @foo '$' True@ where @foo :: Bool -> Int#@ is well-typed.
{-# INLINE ($) #-}
($) :: forall r a (b :: TYPE r). (a -> b) -> a -> b
diff --git a/libraries/base/GHC/Conc/Sync.hs b/libraries/base/GHC/Conc/Sync.hs
index 353b0ac3f2..e27b40dbbd 100644
--- a/libraries/base/GHC/Conc/Sync.hs
+++ b/libraries/base/GHC/Conc/Sync.hs
@@ -629,7 +629,7 @@ newStablePtrPrimMVar (MVar m) = IO $ \s0 ->
case makeStablePtr# (unsafeCoerce# m :: PrimMVar) s0 of
-- Coerce unlifted m :: MVar# RealWorld ()
-- to lifted PrimMVar
- -- apparently because mkStablePtr is not levity-polymorphic
+ -- apparently because mkStablePtr is not representation-polymorphic
(# s1, sp #) -> (# s1, StablePtr sp #)
-----------------------------------------------------------------------------
diff --git a/libraries/base/Unsafe/Coerce.hs b/libraries/base/Unsafe/Coerce.hs
index 5ebc9c637e..0b35eeca1b 100644
--- a/libraries/base/Unsafe/Coerce.hs
+++ b/libraries/base/Unsafe/Coerce.hs
@@ -189,7 +189,7 @@ There are yet more wrinkles
and similarly for unsafeCoerceAddr, unsafeCoerceInt, etc.
-(U10) We also want a levity-polymorphic unsafeCoerce#:
+(U10) We also want a representation-polymorphic unsafeCoerce#:
unsafeCoerce# :: forall (r1 :: RuntimeRep) (r2 :: RuntimeRep)
(a :: TYPE r1) (b :: TYPE r2).
@@ -271,11 +271,11 @@ unsafeCoerce :: forall (a :: Type) (b :: Type) . a -> b
unsafeCoerce x = case unsafeEqualityProof @a @b of UnsafeRefl -> x
unsafeCoerceUnlifted :: forall (a :: TYPE ('BoxedRep 'Unlifted)) (b :: TYPE ('BoxedRep 'Unlifted)) . a -> b
--- Kind-homogeneous, but levity monomorphic (TYPE UnliftedRep)
+-- Kind-homogeneous, but representation-monomorphic (TYPE UnliftedRep)
unsafeCoerceUnlifted x = case unsafeEqualityProof @a @b of UnsafeRefl -> x
unsafeCoerceAddr :: forall (a :: TYPE 'AddrRep) (b :: TYPE 'AddrRep) . a -> b
--- Kind-homogeneous, but levity monomorphic (TYPE AddrRep)
+-- Kind-homogeneous, but representation-monomorphic (TYPE AddrRep)
unsafeCoerceAddr x = case unsafeEqualityProof @a @b of UnsafeRefl -> x
-- | Highly, terribly dangerous coercion from one representation type
diff --git a/libraries/ghc-prim/GHC/Magic.hs b/libraries/ghc-prim/GHC/Magic.hs
index cd9474271d..b032056ed3 100644
--- a/libraries/ghc-prim/GHC/Magic.hs
+++ b/libraries/ghc-prim/GHC/Magic.hs
@@ -94,7 +94,7 @@ lazy x = x
-- that would otherwise be shared are re-evaluated every time they are used. Otherwise,
-- the use of `oneShot` is safe.
--
--- 'oneShot' is representation polymorphic: the type variables may refer to lifted
+-- 'oneShot' is representation-polymorphic: the type variables may refer to lifted
-- or unlifted types.
oneShot :: forall (q :: RuntimeRep) (r :: RuntimeRep)
(a :: TYPE q) (b :: TYPE r).
@@ -108,7 +108,7 @@ oneShot f = f
-- semantically undesirable floating. `runRW#` is inlined, but only very late
-- in compilation after all floating is complete.
--- 'runRW#' is representation polymorphic: the result may have a lifted or
+-- 'runRW#' is levity-polymorphic: the result may have a lifted or
-- unlifted type.
runRW# :: forall (r :: RuntimeRep) (o :: TYPE r).
diff --git a/libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs b/libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs
index 706d4a8c6a..472a4f8557 100644
--- a/libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs
+++ b/libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs
@@ -30,7 +30,7 @@ import Prelude
-- * Type synonyms
----------------------------------------------------------
--- | Levity-polymorphic since /template-haskell-2.17.0.0/.
+-- | Representation-polymorphic since /template-haskell-2.17.0.0/.
type TExpQ :: TYPE r -> Kind.Type
type TExpQ a = Q (TExp a)
diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs
index ff14ea747b..5e0c75151e 100644
--- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs
+++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs
@@ -351,12 +351,12 @@ newtype TExp (a :: TYPE (r :: RuntimeRep)) = TExp
-- In the expression: [|| "foo" ||]
-- In the Template Haskell splice $$([|| "foo" ||])
--
--- Levity-polymorphic since /template-haskell-2.16.0.0/.
+-- Representation-polymorphic since /template-haskell-2.16.0.0/.
-- | Discard the type annotation and produce a plain Template Haskell
-- expression
--
--- Levity-polymorphic since /template-haskell-2.16.0.0/.
+-- Representation-polymorphic since /template-haskell-2.16.0.0/.
unTypeQ :: forall (r :: RuntimeRep) (a :: TYPE r) m . Quote m => m (TExp a) -> m Exp
unTypeQ m = do { TExp e <- m
; return e }
@@ -366,7 +366,7 @@ unTypeQ m = do { TExp e <- m
-- This is unsafe because GHC cannot check for you that the expression
-- really does have the type you claim it has.
--
--- Levity-polymorphic since /template-haskell-2.16.0.0/.
+-- Representation-polymorphic since /template-haskell-2.16.0.0/.
unsafeTExpCoerce :: forall (r :: RuntimeRep) (a :: TYPE r) m .
Quote m => m Exp -> m (TExp a)
unsafeTExpCoerce m = do { e <- m
@@ -913,7 +913,7 @@ sequenceQ = sequence
-- > data Bar a = Bar1 a (Bar a) | Bar2 String
-- > deriving Lift
--
--- Levity-polymorphic since /template-haskell-2.16.0.0/.
+-- Representation-polymorphic since /template-haskell-2.16.0.0/.
class Lift (t :: TYPE r) where
-- | Turn a value into a Template Haskell expression, suitable for use in
-- a splice.