[Git][ghc/ghc][wip/andreask/cast_any] Improve documentation of @Any@ type.

Andreas Klebinger (@AndreasK) gitlab at gitlab.haskell.org
Tue May 28 12:21:32 UTC 2024



Andreas Klebinger pushed to branch wip/andreask/cast_any at Glasgow Haskell Compiler / GHC


Commits:
1be6fd0a by Andreas Klebinger at 2024-05-28T14:05:35+02:00
Improve documentation of @Any@ type.

In particular mention possible uses for non-lifted types.

Fixes #23100.

- - - - -


3 changed files:

- compiler/GHC/Builtin/Types.hs
- libraries/ghc-internal/src/GHC/Internal/Unsafe/Coerce.hs
- libraries/ghc-prim/GHC/Types.hs


Changes:

=====================================
compiler/GHC/Builtin/Types.hs
=====================================
@@ -445,7 +445,15 @@ It has these properties:
   * When instantiated at a lifted type it is inhabited by at least one value,
     namely bottom
 
-  * You can safely coerce any /lifted/ type to Any, and back with unsafeCoerce.
+  * You can safely coerce any /lifted/ type to Any and back with unsafeCoerce.
+    You can safely coerce any /unlifted/ type to Any and back with unsafeCoerceUnlifted.
+    You can coerce /any/ type to Any and back with unsafeCoerce#, but it's only safe when
+    the kinds of both the type and Any match.
+
+    For lifted/unlifted types unsafeCoerce[Unlifted] should be preferred over unsafeCoerce#
+    as they prevent accidentally coercing between types with kinds that don't match.
+
+    See examples in ghc-prim:GHC.Types
 
   * It does not claim to be a *data* type, and that's important for
     the code generator, because the code gen may *enter* a data value


=====================================
libraries/ghc-internal/src/GHC/Internal/Unsafe/Coerce.hs
=====================================
@@ -336,6 +336,10 @@ unsafeCoerceAddr x = case unsafeEqualityProof @a @b of UnsafeRefl -> x
 -- to another. Misuse of this function can invite the garbage collector
 -- to trounce upon your data and then laugh in your face. You don't want
 -- this function. Really.
+--
+-- This becomes more obvious when looking at its actual type:
+-- @forall (r1 :: RuntimeRep) (r2 :: RuntimeRep)  (a :: TYPE r1) (b :: TYPE r2). a -> b@
+-- Which often get's rendered as @a -> b@ in haddock for technical reasons.
 unsafeCoerce# :: forall (r1 :: RuntimeRep) (r2 :: RuntimeRep)
                         (a :: TYPE r1) (b :: TYPE r2).
                  a -> b


=====================================
libraries/ghc-prim/GHC/Types.hs
=====================================
@@ -283,11 +283,43 @@ data Symbol
 *                                                                      *
 ********************************************************************* -}
 
--- | The type constructor 'Any' is type to which you can unsafely coerce any
--- lifted type, and back. More concretely, for a lifted type @t@ and
--- value @x :: t@, @unsafeCoerce (unsafeCoerce x :: Any) :: t@ is equivalent
--- to @x at .
+-- | The type constructor @Any :: forall k. k@ is a type to which you can unsafely coerce any type, and back.
 --
+-- For @unsafeCoerce@ this means for all lifted types @t@ that
+-- @unsafeCoerce (unsafeCoerce x :: Any) :: t@ is equivalent to @x@ and safe.
+--
+-- The same is true for *all* types when using
+-- @
+--   unsafeCoerce# :: forall (r1 :: RuntimeRep) (r2 :: RuntimeRep)
+--                   (a :: TYPE r1) (b :: TYPE r2).
+--                   a -> b
+-- @
+-- but /only/ if you instantiate @r1@ and @r2@ to the /same/ runtime representation.
+-- For example using @(unsafeCoerce# :: forall (a :: TYPE IntRep) (b :: TYPE IntRep). a -> b) x@
+-- is fine, but @(unsafeCoerce# :: forall (a :: TYPE IntRep) (b :: TYPE FloatRep). a -> b)@
+-- will likely cause seg-faults or worse.
+-- For this resason, users should always prefer unsafeCoerce over unsafeCoerce# when possible.
+--
+-- Here are some more examples:
+-- @
+--    bad_a1 :: Any @(TYPE 'IntRep)
+--    bad_a1 = unsafeCoerce# True
+--
+--    bad_a2 :: Any @(TYPE ('BoxedRep 'UnliftedRep))
+--    bad_a2 = unsafeCoerce# True
+-- @
+-- Here @bad_a1@ is bad because we started with @True :: (Bool :: Type)@, represented by a boxed heap pointer,
+-- and coerced it to @a1 :: Any @(TYPE 'IntRep)@, whose representation is a non-pointer integer.
+-- That's why we had to use `unsafeCoerce#`; it is really unsafe because it can change representations.
+-- Similarly @bad_a2@ is bad because although both @True@ and @bad_a2@ are represented by a heap pointer,
+-- @True@ is lifted but @bad_a2@ is not; bugs here may be rather subtle.
+--
+-- If you must use unsafeCoerce# to cast to `Any`, type annotations are recommended
+-- to make sure that @Any@ has the correct kind. As casting between different runtimereps is
+-- unsound. For example to cast a @ByteArray#@ to @Any@ you might use:
+-- @
+--    unsafeCoerce# b :: (Any :: TYPE ('BoxedRep 'Unlifted))
+-- @
 type family Any :: k where { }
 -- See Note [Any types] in GHC.Builtin.Types. Also, for a bit of history on Any see
 -- #10886. Note that this must be a *closed* type family: we need to ensure



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1be6fd0a4f451810be4ea2056f01a88d651a06c0

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1be6fd0a4f451810be4ea2056f01a88d651a06c0
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240528/3bfa011e/attachment-0001.html>


More information about the ghc-commits mailing list