[Git][ghc/ghc][wip/boxed-rep] [skip ci] Update some notes

Andrew Martin gitlab at gitlab.haskell.org
Fri Dec 4 13:21:44 UTC 2020



Andrew Martin pushed to branch wip/boxed-rep at Glasgow Haskell Compiler / GHC


Commits:
185a01b0 by Andrew Martin at 2020-12-04T08:21:29-05:00
[skip ci] Update some notes

- - - - -


3 changed files:

- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Types/RepType.hs
- libraries/ghc-prim/GHC/Types.hs


Changes:

=====================================
compiler/GHC/Builtin/Types/Prim.hs
=====================================
@@ -451,26 +451,28 @@ Note [TYPE and RuntimeRep]
 All types that classify values have a kind of the form (TYPE rr), where
 
     data RuntimeRep     -- Defined in ghc-prim:GHC.Types
-      = LiftedRep
-      | UnliftedRep
+      = BoxedRep Levity
       | IntRep
       | FloatRep
       .. etc ..
 
+    data Levity = Lifted | Unlifted
+
     rr :: RuntimeRep
 
     TYPE :: RuntimeRep -> TYPE 'LiftedRep  -- Built in
 
 So for example:
-    Int        :: TYPE 'LiftedRep
-    Array# Int :: TYPE 'UnliftedRep
+    Int        :: TYPE ('BoxedRep 'Lifted)
+    Array# Int :: TYPE ('BoxedRep 'Unlifted)
     Int#       :: TYPE 'IntRep
     Float#     :: TYPE 'FloatRep
-    Maybe      :: TYPE 'LiftedRep -> TYPE 'LiftedRep
+    Maybe      :: TYPE ('BoxedRep 'Lifted) -> TYPE ('BoxedRep 'Lifted)
     (# , #)    :: TYPE r1 -> TYPE r2 -> TYPE (TupleRep [r1, r2])
 
 We abbreviate '*' specially:
-    type * = TYPE 'LiftedRep
+    type LiftedRep = 'BoxedRep 'Lifted
+    type * = TYPE LiftedRep
 
 The 'rr' parameter tells us how the value is represented at runtime.
 


=====================================
compiler/GHC/Types/RepType.hs
=====================================
@@ -361,10 +361,11 @@ but RuntimeRep has some extra cases:
 data RuntimeRep = VecRep VecCount VecElem   -- ^ a SIMD vector type
                 | TupleRep [RuntimeRep]     -- ^ An unboxed tuple of the given reps
                 | SumRep [RuntimeRep]       -- ^ An unboxed sum of the given reps
-                | LiftedRep       -- ^ lifted; represented by a pointer
-                | UnliftedRep     -- ^ unlifted; represented by a pointer
+                | BoxedRep Levity -- ^ boxed; represented by a pointer
                 | IntRep          -- ^ signed, word-sized value
                 ...etc...
+data Levity     = Lifted
+                | Unlifted
 
 It's all in 1-1 correspondence with PrimRep except for TupleRep and SumRep,
 which describe unboxed products and sums respectively. RuntimeRep is defined
@@ -374,6 +375,13 @@ program, so that every variable has a type that has a PrimRep. For
 example, unarisation transforms our utup function above, to take two Int
 arguments instead of one (# Int, Int #) argument.
 
+Also, note that boxed types are represented slightly differently in RuntimeRep
+and PrimRep. PrimRep just has the nullary LiftedRep and UnliftedRep data
+constructors. RuntimeRep has a BoxedRep data constructor, which accepts a
+Levity. The subtle distinction is that since BoxedRep can accept a variable
+argument, RuntimeRep can talk about levity polymorphic types. PrimRep, by
+contrast, cannot.
+
 See also Note [Getting from RuntimeRep to PrimRep] and Note [VoidRep].
 
 Note [VoidRep]


=====================================
libraries/ghc-prim/GHC/Types.hs
=====================================
@@ -448,6 +448,7 @@ data RuntimeRep = VecRep VecCount VecElem   -- ^ a SIMD vector type
 -- RuntimeRep is intimately tied to TyCon.RuntimeRep (in GHC proper). See
 -- Note [RuntimeRep and PrimRep] in RepType.
 -- See also Note [Wiring in RuntimeRep] in GHC.Builtin.Types
+-- See also Note [TYPE and RuntimeRep] in GHC.Builtin.Type.Prim
 
 -- | Length of a SIMD vector type
 data VecCount = Vec2



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/185a01b0a2522b8197710e339b21179267d4245a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/185a01b0a2522b8197710e339b21179267d4245a
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/20201204/edb83a5c/attachment-0001.html>


More information about the ghc-commits mailing list