Looking at bug #9582

  Associated Type Synonyms do not unfold in InstanceSigs
  https://ghc.haskell.org/trac/ghc/ticket/9582

I found that the given type in an instance signature is compared to the expected type using Type.eqType, which does not seem to know about type families.

https://github.com/ghc/ghc/blob/master/compiler/typecheck/TcInstDcls.lhs

    -- 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)
            ...

https://github.com/ghc/ghc/blob/master/compiler/types/Type.lhs

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]

Question: Is there a (monadic) function for checking type equality which knows about the current type family rules in scope and honors them? Maybe the better question is where to find it, since there should be such a beast (used in the type checker somewhere to compare expected with inferred types).

Cheers,
Andreas (new to the GHC source code)

--
Andreas Abel  <><      Du bist der geliebte Mensch.

Department of Computer Science and Engineering
Chalmers and Gothenburg University, Sweden

andreas.a...@gu.se
http://www2.tcs.ifi.lmu.de/~abel/
_______________________________________________
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs

Reply via email to