[Git][ghc/ghc][master] Document (->) using inferred quantification for its runtime representations.

Marge Bot gitlab at gitlab.haskell.org
Thu May 14 00:06:17 UTC 2020



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
df021fb1 by Baldur Blöndal at 2020-05-13T20:06:06-04:00
Document (->) using inferred quantification for its runtime representations.

Fixes #18142.

- - - - -


4 changed files:

- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/Type.hs


Changes:

=====================================
compiler/GHC/Builtin/Types/Prim.hs
=====================================
@@ -399,9 +399,23 @@ funTyConName = mkPrimTyConName (fsLit "->") funTyConKey funTyCon
 -- | The @(->)@ type constructor.
 --
 -- @
--- (->) :: forall (rep1 :: RuntimeRep) (rep2 :: RuntimeRep).
---         TYPE rep1 -> TYPE rep2 -> *
+-- (->) :: forall {rep1 :: RuntimeRep} {rep2 :: RuntimeRep}.
+--         TYPE rep1 -> TYPE rep2 -> Type
 -- @
+--
+-- The runtime representations quantification is left inferred. This
+-- means they cannot be specified with @-XTypeApplications at .
+--
+-- This is a deliberate choice to allow future extensions to the
+-- function arrow. To allow visible application a type synonym can be
+-- defined:
+--
+-- @
+-- type Arr :: forall (rep1 :: RuntimeRep) (rep2 :: RuntimeRep).
+--             TYPE rep1 -> TYPE rep2 -> Type
+-- type Arr = (->)
+-- @
+--
 funTyCon :: TyCon
 funTyCon = mkFunTyCon funTyConName tc_bndrs tc_rep_nm
   where


=====================================
compiler/GHC/Core/Coercion.hs
=====================================
@@ -292,7 +292,9 @@ tidyCoAxBndrsForUser init_env tcvs
 Note [Function coercions]
 ~~~~~~~~~~~~~~~~~~~~~~~~~
 Remember that
-  (->) :: forall r1 r2. TYPE r1 -> TYPE r2 -> TYPE LiftedRep
+  (->) :: forall {r1} {r2}. TYPE r1 -> TYPE r2 -> TYPE LiftedRep
+whose `RuntimeRep' arguments are intentionally marked inferred to
+avoid type application.
 
 Hence
   FunCo r co1 co2 :: (s1->t1) ~r (s2->t2)


=====================================
compiler/GHC/Core/TyCo/Rep.hs
=====================================
@@ -255,12 +255,15 @@ about it!
 * FFunTy is the data constructor, meaning "full function type".
 
 * The function type constructor (->) has kind
-     (->) :: forall r1 r2. TYPE r1 -> TYPE r2 -> Type LiftedRep
+     (->) :: forall {r1} {r2}. TYPE r1 -> TYPE r2 -> Type LiftedRep
   mkTyConApp ensure that we convert a saturated application
     TyConApp (->) [r1,r2,t1,t2] into FunTy t1 t2
   dropping the 'r1' and 'r2' arguments; they are easily recovered
   from 't1' and 't2'.
 
+* For the time being its RuntimeRep quantifiers are left
+  inferred. This is to allow for it to evolve.
+
 * The ft_af field says whether or not this is an invisible argument
      VisArg:   t1 -> t2    Ordinary function type
      InvisArg: t1 => t2    t1 is guaranteed to be a predicate type,


=====================================
compiler/GHC/Core/Type.hs
=====================================
@@ -1012,9 +1012,10 @@ Note [Representation of function types]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 
 Functions (e.g. Int -> Char) can be thought of as being applications
-of funTyCon (known in Haskell surface syntax as (->)),
+of funTyCon (known in Haskell surface syntax as (->)), (note that
+`RuntimeRep' quantifiers are left inferred)
 
-    (->) :: forall (r1 :: RuntimeRep) (r2 :: RuntimeRep)
+    (->) :: forall {r1 :: RuntimeRep} {r2 :: RuntimeRep}
                    (a :: TYPE r1) (b :: TYPE r2).
             a -> b -> Type
 



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/df021fb15bcef313f30e772997bcb263c8f34078
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/20200513/48daa4ea/attachment-0001.html>


More information about the ghc-commits mailing list