
#9582: Associated Type Synonyms do not unfold in InstanceSigs -------------------------------------+------------------------------------- Reporter: | Owner: andreas.abel | Status: new Type: bug | Milestone: Priority: normal | Version: 7.8.3 Component: Compiler | Keywords: InstanceSigs (Type checker) | TypeFamilies Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by andreas.abel): Relevant snippet: Checking InstanceSigs uses eqType. https://github.com/ghc/ghc/blob/master/compiler/typecheck/TcInstDcls.lhs {{{#!hs -- Check that any type signatures have exactly the right type check_inst_sig hs_ty@(L loc _) = setSrcSpan loc $ do { sig_ty <- tcHsSigType (FunSigCtxt sel_name) hs_ty ; inst_sigs <- xoptM Opt_InstanceSigs ; if inst_sigs then unless (sig_ty `eqType` local_meth_ty) (badInstSigErr sel_name local_meth_ty) else addErrTc (misplacedInstSig sel_name hs_ty) ; return sig_ty } }}} Last commit: https://github.com/ghc/ghc/commit/7fa2ce2043e2faed2b2b545ba5c1c9958954800a According to the documentation, eqType only takes type synonyms into account (not type families). https://github.com/ghc/ghc/blob/master/compiler/types/Type.lhs {{{#!hs eqType :: Type -> Type -> Bool -- ^ Type equality on source types. Does not look through @newtypes@ or -- 'PredType's, but it does look through type synonyms. -- Watch out for horrible hack: See Note [Comparison with OpenTypeKind] eqType t1 t2 = isEqual $ cmpType t1 t2 cmpType :: Type -> Type -> Ordering -- Watch out for horrible hack: See Note [Comparison with OpenTypeKind] cmpType t1 t2 = cmpTypeX rn_env t1 t2 where rn_env = mkRnEnv2 (mkInScopeSet (tyVarsOfType t1 `unionVarSet` tyVarsOfType t2)) cmpTypeX :: RnEnv2 -> Type -> Type -> Ordering -- Main workhorse cmpTypeX env t1 t2 | Just t1' <- coreView t1 = cmpTypeX env t1' t2 | Just t2' <- coreView t2 = cmpTypeX env t1 t2' -- We expand predicate types, because in Core-land we have -- lots of definitions like -- fOrdBool :: Ord Bool -- fOrdBool = D:Ord .. .. .. -- So the RHS has a data type cmpTypeX env (TyVarTy tv1) (TyVarTy tv2) = rnOccL env tv1 `compare` rnOccR env tv2 -- plus congruences... }}} Where to find the type equality check that honors type family instances? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9582#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler