[Git][ghc/ghc][wip/T21623] Wibbles
Simon Peyton Jones (@simonpj)
gitlab at gitlab.haskell.org
Mon Aug 22 23:11:32 UTC 2022
Simon Peyton Jones pushed to branch wip/T21623 at Glasgow Haskell Compiler / GHC
Commits:
d1463b52 by Simon Peyton Jones at 2022-08-23T00:11:35+01:00
Wibbles
But especially: treat Constraint as Typeable
- - - - -
4 changed files:
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Builtin/Uniques.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/Instance/Typeable.hs
Changes:
=====================================
compiler/GHC/Builtin/Types/Prim.hs
=====================================
@@ -233,6 +233,11 @@ unexposedPrimTyCons
= [ eqPrimTyCon
, eqReprPrimTyCon
, eqPhantPrimTyCon
+
+ -- These are un-exposed for now
+ , ctArrowTyCon -- (=>)
+ , ccArrowTyCon -- (==>)
+ , tcArrowTyCon -- (-=>)
]
-- | Primitive 'TyCon's that are defined in, and exported from, GHC.Prim.
@@ -973,6 +978,8 @@ It is an almost-ordinary class defined as if by
* In addition (~) is magical syntax, as ~ is a reserved symbol.
It cannot be exported or imported.
+ * The data constructor of the class is "Eq#", not ":C~"
+
Within GHC, ~ is called eqTyCon, and it is defined in GHC.Builtin.Types.
Historical note: prior to July 18 (~) was defined as a
=====================================
compiler/GHC/Builtin/Uniques.hs
=====================================
@@ -358,7 +358,7 @@ initExitJoinUnique = mkUnique 's' 0
-- * u+1: the TyConRepName of the TyCon
mkPreludeTyConUnique :: Int -> Unique
-mkPreludeTyConUnique i = mkUnique '3' (2*i)
+mkPreludeTyConUnique i = mkUnique '3' (2*i)
tyConRepNameUnique :: Unique -> Unique
tyConRepNameUnique u = incrUnique u
@@ -371,7 +371,7 @@ tyConRepNameUnique u = incrUnique u
-- Prelude data constructors are too simple to need wrappers.
mkPreludeDataConUnique :: Int -> Unique
-mkPreludeDataConUnique i = mkUnique '6' (3*i) -- Must be alphabetic
+mkPreludeDataConUnique i = mkUnique '6' (3*i) -- Must be alphabetic
--------------------------------------------------
dataConTyRepNameUnique, dataConWorkerUnique :: Unique -> Unique
=====================================
compiler/GHC/Tc/Instance/Class.hs
=====================================
@@ -654,7 +654,6 @@ matchTypeable clas [k,t] -- clas = Typeable
| k `eqType` naturalTy = doTyLit knownNatClassName t
| k `eqType` typeSymbolKind = doTyLit knownSymbolClassName t
| k `eqType` charTy = doTyLit knownCharClassName t
- | isConstraintKind t = doTyConApp clas t constraintKindTyCon []
| Just (af,mult,arg,ret) <- splitFunTy_maybe t
, isVisibleAnonArg af = doFunTy clas t mult arg ret
| Just (tc, ks) <- splitTyConApp_maybe t -- See Note [Typeable (T a b c)]
@@ -682,10 +681,9 @@ doFunTy clas ty mult arg_ty ret_ty
doTyConApp :: Class -> Type -> TyCon -> [Kind] -> TcM ClsInstResult
doTyConApp clas ty tc kind_args
| tyConIsTypeable tc
- = do
- return $ OneInst { cir_new_theta = (map (mk_typeable_pred clas) kind_args)
- , cir_mk_ev = mk_ev
- , cir_what = BuiltinTypeableInstance tc }
+ = return $ OneInst { cir_new_theta = map (mk_typeable_pred clas) kind_args
+ , cir_mk_ev = mk_ev
+ , cir_what = BuiltinTypeableInstance tc }
| otherwise
= return NoInstance
where
=====================================
compiler/GHC/Tc/Instance/Typeable.hs
=====================================
@@ -422,9 +422,8 @@ mkTyConRepBinds stuff todo (TypeableTyCon {..})
-- | Is a particular 'TyCon' representable by @Typeable@?. These exclude type
-- families and polytypes.
tyConIsTypeable :: TyCon -> Bool
-tyConIsTypeable tc =
- isJust (tyConRepName_maybe tc)
- && kindIsTypeable (dropForAlls $ tyConKind tc)
+tyConIsTypeable tc = isJust (tyConRepName_maybe tc)
+ && kindIsTypeable (dropForAlls $ tyConKind tc)
-- | Is a particular 'Kind' representable by @Typeable@? Here we look for
-- polytypes and types containing casts (which may be, for instance, a type
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d1463b52fe519774cc19ca5569f785dfb989169a
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d1463b52fe519774cc19ca5569f785dfb989169a
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/20220822/dbd7bbe1/attachment-0001.html>
More information about the ghc-commits
mailing list