[Git][ghc/ghc][wip/T25148] Even more review comments
Ryan Scott (@RyanGlScott)
gitlab at gitlab.haskell.org
Mon Sep 23 12:20:46 UTC 2024
Ryan Scott pushed to branch wip/T25148 at Glasgow Haskell Compiler / GHC
Commits:
4776f2e3 by Ryan Scott at 2024-09-23T08:15:28-04:00
Even more review comments
- - - - -
2 changed files:
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/TyCl/Instance.hs
Changes:
=====================================
compiler/GHC/Tc/Deriv/Generate.hs
=====================================
@@ -1920,9 +1920,12 @@ ambiguous type variables. Here are a couple of examples to illustrate this:
* In this example (from #15637), the class-bound type variable `a` is ambiguous
in the type of `f`:
- class C a where f :: String
- instance C () where f = "foo"
- newtype T = T () deriving C
+ class C a where
+ f :: String -- f :: forall a. C a => String
+ instance C ()
+ where f = "foo"
+ newtype T = T ()
+ deriving C
A naïve attempt and generating a C T instance would be:
@@ -1966,7 +1969,7 @@ ambiguous type variables. Here are a couple of examples to illustrate this:
Note that we use this same approach for resolving ambiguity in default
methods, as described in Note [Default methods in instances] (Wrinkle:
- Ambiguous types from method type signatures) in GHC.Tc.TyCl.Instance.
+ Ambiguous types from vanilla method type signatures) in GHC.Tc.TyCl.Instance.
-}
gen_Newtype_binds :: SrcSpan
=====================================
compiler/GHC/Tc/TyCl/Instance.hs
=====================================
@@ -2230,15 +2230,19 @@ mkDefMethBind loc dfun_id clas sel_id dm_name dm_spec
[ ty | (tcb, ty) <- tyConBinders (classTyCon clas) `zip` inst_tys
, tyConBinderForAllTyFlag tcb /= Inferred ]
- -- When dealing with a vanilla default method, compute the type variables
- -- from the method's type signature. That way, we can bind them with
- -- TypeAbstractions (visible_sel_pats) and use them in the visible type
- -- application (visible_sel_tys). If we are dealing with a generic default
- -- method, don't bother doing any of this. See Note [Default methods in
- -- instances] (Wrinkle: Ambiguous types from method type signatures).
visible_sel_tvbs =
case dm_spec of
- VanillaDM -> filter (\tvb -> binderFlag tvb /= InferredSpec) sel_tvbs
+ -- When dealing with a vanilla default method, compute the type
+ -- variables from the method's type signature. That way, we can bind
+ -- them with TypeAbstractions (visible_sel_pats) and use them in the
+ -- visible type application (visible_sel_tys). See Note [Default methods
+ -- in instances] (Wrinkle: Ambiguous types from vanilla method type
+ -- signatures).
+ VanillaDM -> filter (\tvb -> binderFlag tvb /= InferredSpec) sel_tvbs
+ -- If we are dealing with a generic default method, on the other hand,
+ -- don't bother doing any of this. See Note [Default methods
+ -- in instances] (Wrinkle: Ambiguous types from generic default method
+ -- type signatures).
GenericDM {} -> []
visible_sel_pats = map mk_ty_pat visible_sel_tvbs
visible_sel_tys = map (mkTyVarTy . binderVar) visible_sel_tvbs
@@ -2324,7 +2328,7 @@ post-type-checked code, which took a lot more code, and didn't work for
generic default methods.
-----
--- Wrinkle: Ambiguous types from method type signatures
+-- Wrinkle: Ambiguous types from vanilla method type signatures
-----
In the Bar example above, the ambiguity arises from `v`, a type variable
@@ -2387,19 +2391,37 @@ This resolves the ambiguity and avoids the need for a subtype check. (We also
use a similar trick for resolving ambiguity in GeneralizedNewtypeDeriving: see
also Note [GND and ambiguity] in GHC.Tc.Deriv.Generate.)
-Note that this approach will only work for vanilla default methods and /not/
-for generic default methods. This is because for vanilla default methods, the
-type of the generated $dm* function will always quantify the same type
-variables as the method's original type signature, in the same order and with
-the same specificities. For example, the type of the $dmf function will be:
+-----
+-- Wrinkle: Ambiguous types from generic default method type signatures
+-----
+
+Note that the approach described above (in Wrinkle: Ambiguous types from
+vanilla method type signatures) will only work for vanilla default methods and
+/not/ for generic default methods (i.e., methods using DefaultSignatures). This
+is because for vanilla default methods, the type of the generated $dm* function
+will always quantify the same type variables as the method's original type
+signature, in the same order and with the same specificities. For example, the
+type of the $dmf function will be:
$dmf :: forall t. A t => forall x m. Monoid x => t m -> m
As such, it is guaranteed that the type variables from the method's original
type signature will line up exactly with the type variables from the $dm*
-function (after instantiating all of the class variables). We cannot guarantee
-this property for generic default methods, however. There are a number of
-reasons why this would not work:
+function (after instantiating all of the class variables):
+
+ instance A [] where
+ f @x @m = $dmf @[] @x @m
+
+We cannot guarantee this property for generic default methods, however. As
+such, we must be more conservative and generate code without instantiating any
+of the type variables bound by the method's type signature (only the type
+variables bound by the class header):
+
+ instance A [] where
+ f = $dmf @[]
+
+There are a number of reasons why we cannot reliably instantiate the type
+variables bound by a generic default method's type signature:
* Default methods can quantify type variables in a different order, e.g.,
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4776f2e351147e373adc15430f00d26796c9f2f9
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4776f2e351147e373adc15430f00d26796c9f2f9
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/20240923/a5d34d63/attachment-0001.html>
More information about the ghc-commits
mailing list