[GHC] #15991: Regression in error message when attempting to let bind an existentially quantified type

GHC ghc-devs at haskell.org
Tue Dec 4 02:29:13 UTC 2018


#15991: Regression in error message when attempting to let bind an existentially
quantified type
-------------------------------------+-------------------------------------
           Reporter:  mmailhot       |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.6.3
          Component:  Compiler       |           Version:  8.4.1
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  Poor/confusing
  Unknown/Multiple                   |  error message
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 When attempting to compile the following (invalid) program:

 {{{#!hs
 {-# LANGUAGE ExistentialQuantification #-}

 data Foo = forall a. Foo a

 main :: IO ()
 main =
     let Foo x = Foo 1 in
     return ()
 }}}

 GHC 8.6.2.0 (and 8.6.1.0, 8.4.1.0) gives the following complicated error
 message

 {{{

 Test.hs:7:13: error:
     • Couldn't match expected type ‘p’ with actual type ‘a’
         because type variable ‘a’ would escape its scope
       This (rigid, skolem) type variable is bound by
         a pattern with constructor: Foo :: forall a. a -> Foo,
         in a pattern binding
         at Test.hs:7:9-13
     • In the pattern: Foo x
       In a pattern binding: Foo x = Foo 1
       In the expression: let Foo x = Foo 1 in return ()
   |
 7 |     let Foo x = Foo 1 in
   |
 }}}

 GHC 7.10.1.2 gave a much more helpful and direct error message

 {{{
 Test.hs:7:9:
     My brain just exploded
     I can't handle pattern bindings for existential or GADT data
 constructors.
     Instead, use a case-expression, or do-notation, to unpack the
 constructor.
     In the pattern: Foo x
     In a pattern binding: Foo x = Foo 1
     In the expression: let Foo x = Foo 1 in return ()
 }}}

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


More information about the ghc-tickets mailing list