[Git][ghc/ghc][wip/T25647] rename WildCardTv to NoDefTauTv

Patrick (@soulomoon) gitlab at gitlab.haskell.org
Sun Feb 9 07:28:46 UTC 2025



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


Commits:
f43a47a7 by Patrick at 2025-02-09T15:28:36+08:00
rename WildCardTv to NoDefTauTv

- - - - -


4 changed files:

- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Utils/TcType.hs
- compiler/GHC/Tc/Utils/Unify.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 "_", newWildCardTvDetailsAtLevel)
+               HM_FamPat   -> (fsLit "_", newNoDefTauTvDetailsAtLevel)
                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,
-  newWildCardTvDetailsAtLevel, newTauTvDetailsAtLevel,
+  newNoDefTauTvDetailsAtLevel, newTauTvDetailsAtLevel,
   newMetaDetails, newMetaTyVarName,
   isFilledMetaTyVar_maybe, isFilledMetaTyVar, isUnfilledMetaTyVar,
 
@@ -693,14 +693,20 @@ the thinking.
 *                                                                      *
 ********************************************************************* -}
 
-{- Note [WildCardTv]
+{- Note [NoDefTauTv]
 ~~~~~~~~~~~~~~~~~
-A WildCardTv behaves like a TauTv, except that it can not be defaulted.
-
-It is used for a anonymous wildcard in a type signature, e.g.
-  f :: _ -> Int
-  f = ...
-
+A NoDefTauTv behaves like a TauTv, except that when it is not unified
+with anything, it should not be defaulted.
+
+It is used for a anonymous wildcard in a type family, e.g.
+  type Dix8 :: RuntimeRep -> Type
+  data family Dix8 r
+  newtype instance Dix8 _ = Dix8 Int
+We want to keep `_` polymorphic, so it behaves like a named wildcard.
+
+When unified other type, it should be replaced by the other type, since
+the `not unified with anything` assumption is break. It's property no longer
+holds.
 -}
 
 {- Note [TyVarTv]
@@ -751,7 +757,7 @@ metaInfoToTyVarName :: MetaInfo -> FastString
 metaInfoToTyVarName  meta_info =
   case meta_info of
        TauTv          -> fsLit "t"
-       WildCardTv     -> fsLit "_"
+       NoDefTauTv     -> fsLit "n"
        TyVarTv        -> fsLit "a"
        RuntimeUnkTv   -> fsLit "r"
        CycleBreakerTv -> fsLit "b"
@@ -865,10 +871,10 @@ newTauTvDetailsAtLevel tclvl
                         , mtv_ref   = ref
                         , mtv_tclvl = tclvl }) }
 
-newWildCardTvDetailsAtLevel :: TcLevel -> TcM TcTyVarDetails
-newWildCardTvDetailsAtLevel tclvl
+newNoDefTauTvDetailsAtLevel :: TcLevel -> TcM TcTyVarDetails
+newNoDefTauTvDetailsAtLevel tclvl
   = do { ref <- newMutVar Flexi
-       ; return (MetaTv { mtv_info  = WildCardTv
+       ; return (MetaTv { mtv_info  = NoDefTauTv
                         , mtv_ref   = ref
                         , mtv_tclvl = tclvl }) }
 
@@ -1862,8 +1868,7 @@ defaultTyVar :: DefaultingStrategy
 defaultTyVar def_strat tv
   | not (isMetaTyVar tv )
   || isWildCardMetaTyVar tv
-    -- do not default WildcardTvs, wildcardTvs are are only meant to be unified
-    -- or be on its own but never defaulted.
+    -- do not default NoDefTauTvs see Note [NoDefTauTv]
   || isTyVarTyVar tv
     -- Do not default TyVarTvs. Doing so would violate the invariants
     -- on TyVarTvs; see Note [TyVarTv] in GHC.Tc.Utils.TcMType.


=====================================
compiler/GHC/Tc/Utils/TcType.hs
=====================================
@@ -641,8 +641,8 @@ data MetaInfo
    = TauTv         -- ^ This MetaTv is an ordinary unification variable
                    -- A TauTv is always filled in with a tau-type, which
                    -- never contains any ForAlls.
-   | WildCardTv    -- ^ A variant of TauTv, except that it should not be
-                   -- defaulted.
+   | NoDefTauTv    -- ^ A variant of TauTv, except that it should not be
+                   -- defaulted during generalization. See Note [NoDefTauTv]
    | TyVarTv       -- ^ A variant of TauTv, except that it should not be
                    --   unified with a type, only with a type variable
                    -- See Note [TyVarTv] in GHC.Tc.Utils.TcMType
@@ -672,7 +672,7 @@ instance Outputable MetaInfo where
   ppr RuntimeUnkTv    = text "rutv"
   ppr CycleBreakerTv  = text "cbv"
   ppr (ConcreteTv {}) = text "conc"
-  ppr (WildCardTv)    = text "wc"
+  ppr (NoDefTauTv)    = text "ndtau"
 
 
 -- | What caused us to create a 'ConcreteTv' metavariable?
@@ -1227,7 +1227,7 @@ isMetaTyVar tv
 isWildCardMetaTyVar tv
   | isTyVar tv -- See Note [Coercion variables in free variable lists]
   = case tcTyVarDetails tv of
-        MetaTv { mtv_info = WildCardTv } -> True
+        MetaTv { mtv_info = NoDefTauTv } -> True
         _                                 -> False
   | otherwise = False
 


=====================================
compiler/GHC/Tc/Utils/Unify.hs
=====================================
@@ -2574,9 +2574,12 @@ lhsPriority tv
              CycleBreakerTv -> 0
              TyVarTv        -> 1
              ConcreteTv {}  -> 2
-             WildCardTv     -> 3
-             TauTv          -> 4
-             RuntimeUnkTv   -> 5
+             TauTv          -> 3
+             RuntimeUnkTv   -> 4
+             NoDefTauTv     -> 5 -- ^ when unifying with other, prefer to keep the other.
+                                 -- see Note [NoDefTauTv] for more details.
+                                -- NB. it is not clear to me(soulomoon), RuntimeUnkTv should
+                                -- be higher than NoDefTauTv or not.
 
 {- Note [Unification preconditions]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f43a47a7efcf587f8211455b9dcdc691e8d6c4b5
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/20250209/2c831cad/attachment-0001.html>


More information about the ghc-commits mailing list