[Git][ghc/ghc][wip/T24868] Undo recovery code

Simon Peyton Jones (@simonpj) gitlab at gitlab.haskell.org
Tue Jun 4 14:59:08 UTC 2024



Simon Peyton Jones pushed to branch wip/T24868 at Glasgow Haskell Compiler / GHC


Commits:
dd833da4 by Simon Peyton Jones at 2024-06-04T15:58:33+01:00
Undo recovery code

.. it caused a cascade of follow on errors

- - - - -


1 changed file:

- compiler/GHC/Tc/Gen/App.hs


Changes:

=====================================
compiler/GHC/Tc/Gen/App.hs
=====================================
@@ -532,6 +532,8 @@ tcInstFun do_ql inst_final (tc_fun, fun_ctxt) fun_sigma rn_args
                                    , text "fun_ctxt" <+> ppr fun_ctxt
                                    , text "args:" <+> ppr rn_args
                                    , text "do_ql" <+> ppr do_ql ])
+         -- Recover from fatal failures in kind-checking type arguments
+         -- which are fatal
        ; go emptyVarSet [] [] fun_sigma rn_args }
   where
     fun_orig
@@ -662,14 +664,9 @@ tcInstFun do_ql inst_final (tc_fun, fun_ctxt) fun_sigma rn_args
     -- Rule ITYARG from Fig 4 of the QL paper
     go1 delta acc so_far fun_ty ( ETypeArg { eva_ctxt = ctxt, eva_hs_ty = hs_ty }
                                 : rest_args )
-      = do { mb_res <- attemptM $ tcVTA fun_conc_tvs fun_ty hs_ty
-           ; case mb_res of {
-               Nothing -> -- Failure to kind-check the type, or fun_ty is not a forall;
-                          -- just ignore it the type argument and carry on
-                          go delta acc so_far fun_ty rest_args ;
-               Just (ty_arg, inst_ty) ->
-        do { let arg' = ETypeArg { eva_ctxt = ctxt, eva_hs_ty = hs_ty, eva_ty = ty_arg }
-           ; go delta (arg' : acc) so_far inst_ty rest_args } } }
+      = do { (ty_arg, inst_ty) <- tcVTA fun_conc_tvs fun_ty hs_ty
+           ; let arg' = ETypeArg { eva_ctxt = ctxt, eva_hs_ty = hs_ty, eva_ty = ty_arg }
+           ; go delta (arg' : acc) so_far inst_ty rest_args }
 
     -- Rule IVAR from Fig 4 of the QL paper:
     go1 delta acc so_far fun_ty args@(EValArg {} : _)
@@ -851,24 +848,11 @@ tcVTA conc_tvs fun_ty hs_ty
        ; failWith $ TcRnInvalidTypeApplication fun_ty hs_ty }
 
 -- See Note [Visible type application and abstraction]
-tcVDQ, tcVDQ'
-      :: ConcreteTyVars              -- See Note [Representation-polymorphism checking built-ins]
+tcVDQ :: ConcreteTyVars              -- See Note [Representation-polymorphism checking built-ins]
       -> (ForAllTyBinder, TcType)    -- Function type
       -> LHsExpr GhcRn               -- Argument type
       -> TcM (TcType, TcType)
 tcVDQ conc_tvs (tvb,inner_ty) arg
- = do { mb_res <- attemptM $ tcVDQ' conc_tvs (tvb,inner_ty) arg
-      ; case mb_res of {
-          Just res -> return res ;
-          Nothing  ->
-   do { -- Recovery code. Pretend the type arg is just a meta-tyvar
-      ; let tv = binderVar tvb
-      ; fake_ty_arg <- newFlexiTyVarTy (tyVarKind tv)
-      ; let in_scope  = mkInScopeSet (tyCoVarsOfTypes [mkForAllTy tvb inner_ty,fake_ty_arg])
-            insted_ty = substTyWithInScope in_scope [tv] [fake_ty_arg] inner_ty
-      ; return (fake_ty_arg, insted_ty) } } }
-
-tcVDQ' conc_tvs (tvb, inner_ty) arg
   = do { hs_wc_ty <- expr_to_type arg
        ; tc_inst_forall_arg conc_tvs (tvb, inner_ty) hs_wc_ty }
 



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/dd833da4687e7783fc5c2bb073207bca5abe0474
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/20240604/d4c4e465/attachment-0001.html>


More information about the ghc-commits mailing list