[GHC] #11282: Error warns about non-injectivity of injective type family (was: Injectivity annotation fails in the presence of higher-rank use of constraint family)

GHC ghc-devs at haskell.org
Sat Dec 26 13:33:30 UTC 2015


#11282: Error warns about non-injectivity of injective type family
-------------------------------------+-------------------------------------
        Reporter:  goldfire          |                Owner:
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  7.11
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Old description:

> When I say
>
> {{{
> {-# LANGUAGE TypeFamilies, RankNTypes #-}
>
> module Bug where
>
> import GHC.Exts
>
> type family F a = r | r -> a
> type family G a :: Constraint
>
> meth :: (G a => F a) -> ()
> meth = undefined
> }}}
>
> I get
>
> {{{
> Bug.hs:10:9: error:
>     • Could not deduce: F a ~ F a0
>       from the context: G a0
>         bound by the type signature for:
>                    meth :: G a0 => F a0
>         at Bug.hs:10:9-26
>       NB: ‘F’ is a type function, and may not be injective
>       The type variable ‘a0’ is ambiguous
>     • In the ambiguity check for ‘meth’
>       To defer the ambiguity check to use sites, enable
> AllowAmbiguousTypes
>       In the type signature:
>         meth :: (G a => F a) -> ()
> }}}
>
> The presence of `G a` is critical for exhibiting this bug. If I replace
> `G a` with `Show a` the problem disappears.
>
> This one was actually encountered in an attempt to do Useful Work, not
> just idle typecheckery.

New description:

 When I say

 {{{
 {-# LANGUAGE TypeFamilies, RankNTypes #-}

 module Bug where

 import GHC.Exts

 type family F a = r | r -> a
 type family G a :: Constraint

 meth :: (G a => F a) -> ()
 meth = undefined
 }}}

 I get

 {{{
 Bug.hs:10:9: error:
     • Could not deduce: F a ~ F a0
       from the context: G a0
         bound by the type signature for:
                    meth :: G a0 => F a0
         at Bug.hs:10:9-26
       NB: ‘F’ is a type function, and may not be injective
       The type variable ‘a0’ is ambiguous
     • In the ambiguity check for ‘meth’
       To defer the ambiguity check to use sites, enable
 AllowAmbiguousTypes
       In the type signature:
         meth :: (G a => F a) -> ()
 }}}

 The presence of `G a` is critical for exhibiting this bug. If I replace `G
 a` with `Show a` the problem disappears.

 This one was actually encountered in an attempt to do Useful Work, not
 just idle typecheckery.

 EDIT: Actually, I understand why this program should be rejected
 (comment:1), but the error message is surely misleading and should be
 fixed.

--

Comment (by goldfire):

 I had figured that out (in rather less detail) by looking at the case
 without the injective type family. But the original error message is still
 warning me about a type family that isn't injective! So I think this boils
 down to adding a bit more logic to !TcErrors to print out an error about
 untouchable variables here instead of non-injective type families.

 I've modified the title and description to make this more clear.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11282#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list