
#15039: Bizarre pretty-printing of inferred Coercible constraint in partial type signature -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.4.1 checker) | Keywords: Resolution: | PartialTypeSignatures Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): #15039 I know what is going on here. When we first introduced explicit equalities Richard arranged to make the pretty-printer conceal some of the menagerie, with some ad-hoc rules sketched in `IfaceType`: {{{ Note [Equality predicates in IfaceType] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ GHC has several varieties of type equality (see Note [The equality types story] in TysPrim for details). In an effort to avoid confusing users, we suppress the differences during "normal" pretty printing. Specifically we display them like this: Predicate Pretty-printed as Homogeneous case Heterogeneous case ---------------- ----------------- ------------------- (~) eqTyCon ~ N/A (~~) heqTyCon ~ ~~ (~#) eqPrimTyCon ~# ~~ (~R#) eqReprPrimTyCon Coercible Coercible By "homogeneeous case" we mean cases where a hetero-kinded equality (all but the first above) is actually applied to two identical kinds. Unfortunately, determining this from an IfaceType isn't possible since we can't see through type synonyms. Consequently, we need to record whether this particular application is homogeneous in IfaceTyConSort for the purposes of pretty-printing. All this suppresses information. To get the ground truth, use -dppr-debug (see 'print_eqs' in 'ppr_equality'). See Note [The equality types story] in TysPrim. }}} There's a flag to control this: `-fprint-equality-relations`, and using that flag makes both oddities go away. In this particular case, although it displays `Coercible a b`, it is really pretty printing `a ~R# b`! And that is why the kind looks wrong: it's the kind of `a ~R# b`. So concealing the reality is jolly confusing here. Moreover, for reasons I don't understand, `-fprint-explicit-kinds` affects the behhaviour too, hence oddness (2). It's all in `IfaceType.ppr_equality`, which I reproduce below {{{ ppr_equality :: TyPrec -> IfaceTyCon -> [IfaceType] -> Maybe SDoc ppr_equality ctxt_prec tc args | hetero_eq_tc , [k1, k2, t1, t2] <- args = Just $ print_equality (k1, k2, t1, t2) | hom_eq_tc , [k, t1, t2] <- args = Just $ print_equality (k, k, t1, t2) | otherwise = Nothing where homogeneous = case ifaceTyConSort $ ifaceTyConInfo tc of IfaceEqualityTyCon -> True _other -> False -- True <=> a heterogeneous equality whose arguments -- are (in this case) of the same kind tc_name = ifaceTyConName tc pp = ppr_ty hom_eq_tc = tc_name `hasKey` eqTyConKey -- (~) hetero_eq_tc = tc_name `hasKey` eqPrimTyConKey -- (~#) || tc_name `hasKey` eqReprPrimTyConKey -- (~R#) || tc_name `hasKey` heqTyConKey -- (~~) print_equality args = sdocWithDynFlags $ \dflags -> getPprStyle $ \style -> print_equality' args style dflags print_equality' (ki1, ki2, ty1, ty2) style dflags | print_eqs -- No magic, just print the original TyCon = ppr_infix_eq (ppr tc) | hetero_eq_tc , print_kinds || not homogeneous = ppr_infix_eq (text "~~") | otherwise = if tc_name `hasKey` eqReprPrimTyConKey then pprIfacePrefixApp ctxt_prec (text "Coercible") [pp TyConPrec ty1, pp TyConPrec ty2] else pprIfaceInfixApp ctxt_prec (char '~') (pp TyOpPrec ty1) (pp TyOpPrec ty2) where ppr_infix_eq eq_op = pprIfaceInfixApp ctxt_prec eq_op (parens (pp TopPrec ty1 <+> dcolon <+> pp TyOpPrec ki1)) (parens (pp TopPrec ty2 <+> dcolon <+> pp TyOpPrec ki2)) print_kinds = gopt Opt_PrintExplicitKinds dflags print_eqs = gopt Opt_PrintEqualityRelations dflags || dumpStyle style || debugStyle style }}} What to do? I'm not sure. But that's what is going on. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15039#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler