[Git][ghc/ghc][wip/T24817a] Wibbles

Simon Peyton Jones (@simonpj) gitlab at gitlab.haskell.org
Fri Aug 16 16:30:20 UTC 2024



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


Commits:
ca18ca02 by Simon Peyton Jones at 2024-08-16T17:29:59+01:00
Wibbles

- - - - -


2 changed files:

- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Tc/Zonk/Type.hs


Changes:

=====================================
compiler/GHC/Builtin/Types.hs
=====================================
@@ -91,7 +91,7 @@ module GHC.Builtin.Types (
         cTupleSelId, cTupleSelIdName,
 
         -- * Any
-        anyTyCon, anyTy, anyTypeOfKind,
+        anyTyCon, anyTy, anyTypeOfKind, zonkAnyTyCon,
 
         -- * Recovery TyCon
         makeRecoveryTyCon,
@@ -184,7 +184,7 @@ import GHC.Core.ConLike
 import GHC.Core.TyCon
 import GHC.Core.Class     ( Class, mkClass )
 import GHC.Core.Map.Type  ( TypeMap, emptyTypeMap, extendTypeMap, lookupTypeMap )
-import qualified GHC.Core.TyCo.Rep as TyCoRep (Type(TyConApp))
+import qualified GHC.Core.TyCo.Rep as TyCoRep ( Type(TyConApp), mkNakedFunTy )
 
 import GHC.Types.TyThing
 import GHC.Types.SourceText
@@ -516,8 +516,10 @@ zonkAnyTyCon = mkFamilyTyCon zonkAnyTyConName binders res_kind Nothing
                          NotInjective
   where
     binders@[kv] = mkTemplateKindTyConBinders [liftedTypeKind]
+
+    res_kind :: Kind
     res_kind = -- Nat -> k
-               mkFunTy natTy mkTyVarTy (binderVar kv)
+               TyCoRep.mkNakedFunTy FTF_T_T naturalTy (mkTyVarTy (binderVar kv))
 
 
 -- | Make a fake, recovery 'TyCon' from an existing one.


=====================================
compiler/GHC/Tc/Zonk/Type.hs
=====================================
@@ -469,8 +469,8 @@ commitFlexi tv zonked_kind
            -> do { addErr $ TcRnZonkerMessage (ZonkerCannotDefaultConcrete origin)
                  ; return (anyTypeOfKind zonked_kind) }
            | otherwise
-           -> do { traceTc "Defaulting flexi tyvar to Any:" (pprTyVar tv)
-                 ; return (anyTypeOfKind zonked_kind) }
+           -> do { traceTc "Defaulting flexi tyvar to ZonkAny:" (pprTyVar tv)
+                 ; newZonkAnyType zonked_kind }
 
          RuntimeUnkFlexi
            -> do { traceTc "Defaulting flexi tyvar to RuntimeUnk:" (pprTyVar tv)



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

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


More information about the ghc-commits mailing list