[GHC] #12832: GHC infers too simplified contexts

GHC ghc-devs at haskell.org
Sat Nov 12 22:36:19 UTC 2016


#12832: GHC infers too simplified contexts
-------------------------------------+-------------------------------------
        Reporter:  danilo2           |                Owner:
            Type:  bug               |               Status:  new
        Priority:  high              |            Milestone:
       Component:  Compiler          |              Version:  8.0.1
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  Incorrect         |  Unknown/Multiple
  error/warning at compile-time      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Description changed by danilo2:

@@ -5,1 +5,1 @@
-
+ {-# LANGUAGE NoMonomorphismRestriction #-}

New description:

 I'm almost sure it was working well in GHC 7.*.
 Let's consider this simple example:

 {{{
 {-# LANGUAGE NoMonomorphismRestriction #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE EmptyDataDecls #-}

 module Main where

 import Prelude

 class Monad m => Foo m
 class Monad m => Bar m
 class Monad m => Baz m

 data IM a
 data I

 impossible = error "impossible"

 class Test m a where test :: a -> m ()
 instance {-# OVERLAPPABLE #-} (Foo m, Bar m, Baz m) => Test m  a where
 test _  = return ()
 instance {-# OVERLAPPABLE #-}                          Test IM a where
 test   = impossible

 class    Run m a where run :: a -> m ()

 main :: IO ()
 main = return ()
 }}}

 it compiles and runs fine. What should happen when we add the following
 def?

 {{{
 instance Run m Int where
     run = test
 }}}

 We SHOULD get an error that there is `No instance for (Test m Int) arising
 from a use of ‘test’`. Instead we get very strange one `No instance for
 (Foo m) arising from a use of ‘test’.` If we add it, we get the next one
 `No instance for (Bar m) arising from a use of ‘test’.` etc ...

 If we comment out the first overlappable instance, we get proper error
 about missing `Test m Int` context. In fact if we add context `Test m Int`
 it works in every case, only the inferred error is just wrong.

 This is a serious problem and here is why. Imagine that we create an API
 for end-user and we give him the `test` function. Moreover, we know that
 expanding the context would not bring any further info unless `m` is
 known. If we create such "impossible" instances like in the example, user
 will get a very simple error message about a missing context. Right now
 user gets a big error stack about missing expanded contexts instead of
 simple one.

--

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


More information about the ghc-tickets mailing list