[GHC] #14000: Out of scope errors with type families do not mention scope

GHC ghc-devs at haskell.org
Thu Jul 20 08:50:35 UTC 2017


#14000: Out of scope errors with type families do not mention scope
-------------------------------------+-------------------------------------
           Reporter:  EyalLotem      |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.0.1
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 {{{
 {-# LANGUAGE TypeFamilies #-}
 class C a where
     type T a
     c :: a -> T a
 main = c noSuchThing
 }}}

 yields:
 {{{
 test_bad_error.hs:6:1: error:
     • Couldn't match expected type ‘T a’ with actual type ‘T a0’
       NB: ‘T’ is a type function, and may not be injective
       The type variable ‘a0’ is ambiguous
     • In the ambiguity check for the inferred type for ‘main’
       To defer the ambiguity check to use sites, enable
 AllowAmbiguousTypes
       When checking the inferred type
         main :: forall a. T a
 }}}

 This makes simple out-of-scope error seem very perplexing and is a huge
 regression in error quality.

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


More information about the ghc-tickets mailing list