[GHC] #12406: New not-in-scope behaviour + deferred typed holes = disappearing error messages

GHC ghc-devs at haskell.org
Mon Jul 18 11:07:23 UTC 2016


#12406: New not-in-scope behaviour + deferred typed holes = disappearing error
messages
-------------------------------------+-------------------------------------
        Reporter:  ertes             |                Owner:
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  8.0.1
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Description changed by ertes:

@@ -1,2 +1,1 @@
- The following code snippet (using the [https://hackage.haskell.org/package
- /ref-tf ref-tf library]) is well-typed, and GHC is fine with it:
+ The following code snippet is well-typed, and GHC is fine with it:
@@ -5,0 +4,2 @@
+ {-# LANGUAGE TypeFamilies #-}
+
@@ -6,1 +7,11 @@
- import Control.Monad.Ref
+ import Data.IORef
+
+ class MonadRef m where
+     type Ref m :: * -> *
+     newRef :: a -> m (Ref m a)
+     readRef :: Ref m a -> m a
+
+ instance MonadRef IO where
+     type Ref IO = IORef
+     newRef = newIORef
+     readRef = readIORef
@@ -12,2 +23,3 @@
- However, if one comments out the first line, then GHC treats `join` as a
- typed hole due to #10569, but fails to infer its type, causing errors:
+ However, if one removes the import of `Control.Monad`, then GHC treats
+ `join` as a typed hole due to #10569, but fails to infer its type, causing
+ errors:
@@ -16,2 +28,2 @@
- test.hs:10:8-23: error: …
-     • Couldn't match type ‘Ref m0’ with ‘GHC.IORef.IORef’
+ test.hs:17:8-23: error: …
+     • Couldn't match type ‘Ref m0’ with ‘IORef’
@@ -19,1 +31,1 @@
- test.hs:10:29-32: error: …
+ test.hs:17:29-32: error: …
@@ -24,2 +36,2 @@
- holes` is in effect, only the type error is reported leaving the user (at
- least me) puzzled.
+ holes` is in effect, only the type error is reported and the scope error
+ just vanishes, leaving the user (at least me) puzzled.

New description:

 The following code snippet is well-typed, and GHC is fine with it:

 {{{#!hs
 {-# LANGUAGE TypeFamilies #-}

 import Control.Monad  -- comment this out to cause error
 import Data.IORef

 class MonadRef m where
     type Ref m :: * -> *
     newRef :: a -> m (Ref m a)
     readRef :: Ref m a -> m a

 instance MonadRef IO where
     type Ref IO = IORef
     newRef = newIORef
     readRef = readIORef

 main :: IO ()
 main = newRef (pure ()) >>= join . readRef
 }}}

 However, if one removes the import of `Control.Monad`, then GHC treats
 `join` as a typed hole due to #10569, but fails to infer its type, causing
 errors:

 {{{
 test.hs:17:8-23: error: …
     • Couldn't match type ‘Ref m0’ with ‘IORef’
       ...
 test.hs:17:29-32: error: …
     Variable not in scope: join :: m0 (f0 ()) -> IO ()
 }}}

 By default the not-in-scope error is reported, but if `-fdefer-typed-
 holes` is in effect, only the type error is reported and the scope error
 just vanishes, leaving the user (at least me) puzzled.

 Not-in-scope errors should ''always'' be reported.

--

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


More information about the ghc-tickets mailing list