[Git][ghc/ghc][wip/T25647] use TyVarTv for wildcard in HM_FamPat

Patrick (@soulomoon) gitlab at gitlab.haskell.org
Wed Feb 12 09:52:13 UTC 2025



Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC


Commits:
638d6763 by Patrick at 2025-02-12T17:51:58+08:00
use TyVarTv for wildcard in HM_FamPat

- - - - -


3 changed files:

- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- testsuite/tests/typecheck/should_compile/T25647a.hs


Changes:

=====================================
compiler/GHC/Tc/Gen/HsType.hs
=====================================
@@ -2233,7 +2233,7 @@ tcAnonWildCardOcc is_extra (TcTyMode { mode_holes = Just (hole_lvl, hole_mode) }
      -- See Note [Wildcard names]
      (wc_nm, mk_wc_details) = case hole_mode of
                HM_Sig      -> (fsLit "w", newTauTvDetailsAtLevel)
-               HM_FamPat   -> (fsLit "_", newNoDefTauTvDetailsAtLevel)
+               HM_FamPat   -> (fsLit "_", newTyVarTvDetailsAtLevel)
                HM_VTA      -> (fsLit "w", newTauTvDetailsAtLevel)
                HM_TyAppPat -> (fsLit "_", newTauTvDetailsAtLevel)
 


=====================================
compiler/GHC/Tc/Utils/TcMType.hs
=====================================
@@ -34,7 +34,7 @@ module GHC.Tc.Utils.TcMType (
 
   newMultiplicityVar,
   readMetaTyVar, writeMetaTyVar, writeMetaTyVarRef,
-  newNoDefTauTvDetailsAtLevel, newTauTvDetailsAtLevel,
+  newTyVarTvDetailsAtLevel, newTauTvDetailsAtLevel,
   newMetaDetails, newMetaTyVarName,
   isFilledMetaTyVar_maybe, isFilledMetaTyVar, isUnfilledMetaTyVar,
 
@@ -901,10 +901,10 @@ newTauTvDetailsAtLevel tclvl
                         , mtv_ref   = ref
                         , mtv_tclvl = tclvl }) }
 
-newNoDefTauTvDetailsAtLevel :: TcLevel -> TcM TcTyVarDetails
-newNoDefTauTvDetailsAtLevel tclvl
+newTyVarTvDetailsAtLevel :: TcLevel -> TcM TcTyVarDetails
+newTyVarTvDetailsAtLevel tclvl
   = do { ref <- newMutVar Flexi
-       ; return (MetaTv { mtv_info  = NoDefTauTv
+       ; return (MetaTv { mtv_info  = TyVarTv
                         , mtv_ref   = ref
                         , mtv_tclvl = tclvl }) }
 


=====================================
testsuite/tests/typecheck/should_compile/T25647a.hs
=====================================
@@ -94,5 +94,23 @@ dix9 (Dix9 x) = x
 -- anonymous wildcard should work
 class DixC10 a where
   type Dix10 a
-instance DixC10 Int where
+-- instance DixC10 Int where -- type is not allowed to match against a wildcard
+instance DixC10 a where
   type Dix10 _ = Bool
+
+-- wildcard can match with type variable however
+data Tree a = Leaf a | Node (Tree (G a a)) (Tree (G a a))
+class D a where
+  type G a b
+
+class C a where { type T a b }
+
+instance C (p,p) where
+    type T (_,_) b = Int
+
+instance C (Maybe [a]) where
+  type T (Maybe [a]) _ = a->a
+
+instance C (Tree a) where
+  type T (Tree _) b = b->b
+



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/638d6763d0b972f3c9a0e2c4218d8c7ce34dc800
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/20250212/eb82984b/attachment-0001.html>


More information about the ghc-commits mailing list