[GHC] #11059: panic in type hole when using 'ScopedTypeVariables'

GHC ghc-devs at haskell.org
Thu Nov 5 15:05:59 UTC 2015


#11059: panic in type hole when using 'ScopedTypeVariables'
-------------------------------------+-------------------------------------
        Reporter:  dimitri-xyz       |                Owner:
            Type:  bug               |               Status:  closed
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  7.10.2
      Resolution:  duplicate         |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:  #10045            |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Changes (by thomie):

 * status:  new => closed
 * resolution:   => duplicate
 * os:  MacOS X => Unknown/Multiple
 * related:   => #10045


Comment:

 goldfire: you can uncomment `BUILD_EXTRA_PKGS=YES` in your `mk/build.mk`
 file. `make` will then also build the packages that have tag=extra in the
 `./packages` file (currently `parallel` and `stm`).

 After doing so, and installing all the other packages, I get:
 {{{
 $ ~/ghc-quick/inplace/bin/ghc-stage2 Test.hs
 [1 of 1] Compiling Main             ( Test.hs, Test.o )

 Test.hs:38:17: error:
     Found type wildcard ‘_’
       standing for ‘seqNum
                     -> PQueue k value
                     -> IORef (seqNum, PQueue k value)
                     -> Proxy x' x () value m ()’
     Where: ‘value’ is a rigid type variable bound by
                    the type signature for:
                      mkConsecutive :: (Ord seqNum, Num seqNum) =>
                                       (value -> seqNum) -> Int -> Pipe
 value value IO ()
                    at Test.hs:22:25
            ‘seqNum’ is a rigid type variable bound by
                     the type signature for:
                       mkConsecutive :: (Ord seqNum, Num seqNum) =>
                                        (value -> seqNum) -> Int -> Pipe
 value value IO ()
                     at Test.hs:22:31
            ‘k’ is a rigid type variable bound by
                the inferred type of
                next :: (Ord k, MonadIO m) =>
                        seqNum
                        -> PQueue k value
                        -> IORef (seqNum, PQueue k value)
                        -> Proxy x' x () value m ()
                at Test.hs:39:9
            ‘m’ is a rigid type variable bound by
                the inferred type of
                next :: (Ord k, MonadIO m) =>
                        seqNum
                        -> PQueue k value
                        -> IORef (seqNum, PQueue k value)
                        -> Proxy x' x () value m ()
                at Test.hs:39:9
            ‘x'’ is a rigid type variable bound by
                 the inferred type of
                 next :: (Ord k, MonadIO m) =>
                         seqNum
                         -> PQueue k value
                         -> IORef (seqNum, PQueue k value)
                         -> Proxy x' x () value m ()
                 at Test.hs:39:9
            ‘x’ is a rigid type variable bound by
                the inferred type of
                next :: (Ord k, MonadIO m) =>
                        seqNum
                        -> PQueue k value
                        -> IORef (seqNum, PQueue k value)
                        -> Proxy x' x () value m ()
                at Test.hs:39:9
     To use the inferred type, enable PartialTypeSignatures
     Relevant bindings include
       maxSize :: Int (bound at Test.hs:23:17)
       f :: value -> seqNum (bound at Test.hs:23:15)
       mkConsecutive :: (value -> seqNum) -> Int -> Pipe value value IO ()
         (bound at Test.hs:23:1)
     In the type signature for:
       next :: _
     In an equation for ‘mkConsecutive’:
         mkConsecutive f maxSize
           = do { msg1 <- await;
                  yield msg1;
                  curRef <- liftIO $ newIORef (f msg1, empty);
                  .... }
           where
               next :: _
               next cur pq curRef
                 = case minView pq of {
                     Nothing -> liftIO $ writeIORef curRef ...
                     Just (minVal, pq') -> ... }

 Test.hs:39:9: error:
     No instance for (Ord k)
     When checking that ‘next’ has the inferred type
       next :: forall k (m :: * -> *) x' x.
               seqNum
               -> PQueue k value
               -> IORef (seqNum, PQueue k value)
               -> Proxy x' x () value m ()
     Probable cause: the inferred type is ambiguous
     In an equation for ‘mkConsecutive’:
         mkConsecutive f maxSize
           = do { msg1 <- await;
                  yield msg1;
                  curRef <- liftIO $ newIORef (f msg1, empty);
                  .... }
           where
               next :: _
               next cur pq curRef
                 = case minView pq of {
                     Nothing -> liftIO $ writeIORef curRef ...
                     Just (minVal, pq') -> ... }
 }}}

 So this indeed looks like a duplicate of #10045: a combination of a typed
 hole and a missing instance.

 dimitri-xyz: as a workaround, you can use `-fdefer-type-errors`, and
 you'll see those same two errors as warnings.

 I'm not adding another test, because of all the dependencies, and because
 we have plenty of tests for this bug already (another one in #10999).

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


More information about the ghc-tickets mailing list