[GHC] #7437: peculiar behaviour with default instances and type variables

GHC ghc-devs at haskell.org
Mon Nov 24 20:46:10 UTC 2014


#7437: peculiar behaviour with default instances and type variables
-------------------------------------+-------------------------------------
              Reporter:  bos         |            Owner:  simonpj
                  Type:  bug         |           Status:  infoneeded
              Priority:  normal      |        Milestone:  7.10.1
             Component:  Compiler    |          Version:  7.6.1
  (Type checker)                     |         Keywords:
            Resolution:              |     Architecture:  Unknown/Multiple
      Operating System:              |       Difficulty:  Unknown
  Unknown/Multiple                   |       Blocked By:
       Type of failure:  GHC         |  Related Tickets:
  accepts invalid program            |
             Test Case:              |
              Blocking:              |
Differential Revisions:              |
-------------------------------------+-------------------------------------
Changes (by thomie):

 * status:  new => infoneeded
 * component:  Compiler => Compiler (Type checker)


Comment:

 Uncommenting the `FlexibleInstances` pragma does not have an effect on the
 error message with ghc HEAD (or ghc-7.8.3), and the message also seems
 much improved:

 {{{
 $ cat test.hs
 {-# LANGUAGE DefaultSignatures, FlexibleContexts, DeriveGeneric #-}
 {-# LANGUAGE FlexibleInstances #-}

 module Whee where
 ...

 $ ghc-7.9.20141121 test.hs
 [1 of 1] Compiling Whee             ( test.hs, test.o )

 test.hs:12:1:
     Could not deduce (Put a0)
     from the context (Put a, Generic t, GPut (Rep t))
       bound by the type signature for
                  put :: (Put a, Generic t, GPut (Rep t)) => t -> [()]
       at test.hs:(12,1)-(17,21)
     The type variable ‘a0’ is ambiguous
     In the ambiguity check for the type signature for ‘put’:
       put :: forall a.
              Put a =>
              forall t. (Generic t, GPut (Rep t)) => t -> [()]
     To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
     When checking the class method: put :: a -> [()]
     In the class declaration for ‘Put’
 }}}

 Does that means this issue is resolved?

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


More information about the ghc-tickets mailing list