[GHC] #13490: Ambiguous types with constraints on new variables

GHC ghc-devs at haskell.org
Mon Mar 27 22:59:43 UTC 2017


#13490: Ambiguous types with constraints on new variables
-------------------------------------+-------------------------------------
           Reporter:  crockeea       |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.0.2
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  GHC rejects
  Unknown/Multiple                   |  valid program
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 The following code fails to compile:


 {{{
 {-# LANGUAGE FlexibleContexts, TypeFamilies #-}

 import Data.Typeable

 type family Foo a

 data C a

 foo :: (Typeable (C z), z ~ Foo zp) => C zp
 foo = undefined
 }}}

 with the error

 {{{
     • Could not deduce (Typeable z)
       from the context: (Typeable (C z), z ~ Foo zp)
         bound by the type signature for:
                    foo :: (Typeable (C z), z ~ Foo zp) => C zp
         at Bug.hs:(9,8)-(10,9)
     • In the ambiguity check for ‘foo’
       To defer the ambiguity check to use sites, enable
 AllowAmbiguousTypes
       In the type signature:
         foo :: (Typeable (C z), z ~ Foo zp) => C zp
 }}}

 It's quite unclear why GHC feels thta it needs `Typeable z`. The code
 compiles if I change the `Typeable` constraint to `Typeable (C (Foo zp))`,
 which should be identical to what I wrote.

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


More information about the ghc-tickets mailing list