[Git][ghc/ghc][wip/sand-witch/forall-tc-fix-th] Fix TH handling in `pat_to_type_pat` function (#24571)

Andrei Borzenkov (@sand-witch) gitlab at gitlab.haskell.org
Thu Mar 21 09:12:28 UTC 2024



Andrei Borzenkov pushed to branch wip/sand-witch/forall-tc-fix-th at Glasgow Haskell Compiler / GHC


Commits:
e5ec2e06 by Andrei Borzenkov at 2024-03-21T13:09:09+04:00
Fix TH handling in `pat_to_type_pat` function (#24571)

There was missing case for `SplicePat` in `pat_to_type_at` function,
hence patterns with splicing that checked against `forall->` doesn't work
properly because they fall into the "illegal pattern" case.

Code example that is now accepted:

  g :: forall a -> ()
  g $([p| a |]) = ()

- - - - -


3 changed files:

- compiler/GHC/Tc/Gen/Pat.hs
- + testsuite/tests/th/T24571.hs
- testsuite/tests/th/all.T


Changes:

=====================================
compiler/GHC/Tc/Gen/Pat.hs
=====================================
@@ -534,6 +534,9 @@ pat_to_type_pat (SigPat _ pat sig_ty)
 pat_to_type_pat (ParPat _ pat)
   = do { HsTP x t <- pat_to_type_pat (unLoc pat)
        ; return (HsTP x (noLocA (HsParTy noAnn t))) }
+pat_to_type_pat (SplicePat (HsUntypedSpliceTop mod_finalizers pat) splice) = do
+      { HsTP x t <- pat_to_type_pat pat
+      ; return (HsTP x (noLocA (HsSpliceTy (HsUntypedSpliceTop mod_finalizers t) splice))) }
 pat_to_type_pat pat =
   -- There are other cases to handle (ConPat, ListPat, TuplePat, etc), but these
   -- would always be rejected by the unification in `tcHsTyPat`, so it's fine to


=====================================
testsuite/tests/th/T24571.hs
=====================================
@@ -0,0 +1,5 @@
+{-# LANGUAGE TemplateHaskell, RequiredTypeArguments #-}
+module T24571 where
+
+g :: forall a -> ()
+g $([p| a |]) = ()


=====================================
testsuite/tests/th/all.T
=====================================
@@ -605,3 +605,4 @@ test('T14032a', normal, compile, [''])
 test('T14032e', normal, compile_fail, ['-dsuppress-uniques'])
 test('ListTuplePunsTH', [only_ways(['ghci']), extra_files(['ListTuplePunsTH.hs', 'T15843a.hs'])], ghci_script, ['ListTuplePunsTH.script'])
 test('T24559', normal, compile, [''])
+test('T24571', normal, compile, [''])



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

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


More information about the ghc-commits mailing list