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

GHC ghc-devs at haskell.org
Tue Nov 3 23:25:22 UTC 2015


#11059: panic in type hole when using 'ScopedTypeVariables'
----------------------------------------+---------------------------------
           Reporter:  dimitri-xyz       |             Owner:
               Type:  bug               |            Status:  new
           Priority:  normal            |         Milestone:
          Component:  Compiler          |           Version:  7.10.2
           Keywords:                    |  Operating System:  MacOS X
       Architecture:  Unknown/Multiple  |   Type of failure:  None/Unknown
          Test Case:                    |        Blocked By:
           Blocking:                    |   Related Tickets:
Differential Rev(s):                    |         Wiki Page:
----------------------------------------+---------------------------------
 I got the following error message:

 {{{
 [1 of 1] Compiling Main             ( ghc-bug.hs, ghc-bug.o )

 ghc-bug.hs:27:5:
     Couldn't match type ‘m’ with ‘IO’
       ‘m’ is untouchable
         inside the constraints (Ord seqNum, Num seqNum)
         bound by the type signature for
                    mkConsecutive :: (Ord seqNum, Num seqNum) =>
                                     (value -> seqNum) -> Int -> Pipe value
 value IO ()
         at ghc-bug.hs:22:18-116ghc: panic! (the 'impossible' happened)
   (GHC version 7.10.2 for x86_64-apple-darwin):
         No skolem info: m_a1qw[sk]

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

 }}}

 when compiling the following file:


 {{{
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE ScopedTypeVariables #-}

 import           Data.List
 import           Data.IORef
 import           Control.Monad


 import           Data.PriorityQueue.FingerTree as PQ

 import           Pipes
 import           Pipes.Concurrent
 import qualified Pipes.Prelude                   as P



 main = runEffect $ P.stdinLn >-> mkConsecutive length 20 >-> P.stdoutLn

 -- Ensure messages are received in order.
 -- FIX ME!! buffer should allow at most 20 messages.
 mkConsecutive :: forall value seqNum. (Ord seqNum, Num seqNum) => (value
 -> seqNum) -> Int -> Pipe value value IO ()
 mkConsecutive f maxSize = do
     msg1 <- await
     yield msg1
     curRef <- liftIO $ newIORef (f msg1, PQ.empty)
     forever $ do
         msg <- await
         (cur, pq) <- liftIO $ readIORef curRef
         let pq' = PQ.add (f msg) msg pq
         next cur pq' curRef

     where
         -- next :: (Ord seqNum, Num seqNum) => seqNum
         --      -> PQ.PQueue seqNum value
         --      -> IORef (seqNum, PQ.PQueue seqNum avalue)
         --      -> Pipe value value IO ()
         next :: _
         next cur pq curRef = case PQ.minView pq of
             Nothing            -> liftIO $ writeIORef curRef (cur, pq)
             Just (minVal, pq') -> if f minVal == cur + 1
                         then do
                                 yield minVal
                                 next (f minVal) pq' curRef
                         else do
                                 liftIO $ writeIORef curRef (cur, pq)

 }}}

 I am using Pipes-4.1.6 and fingertree-0.1.1.0.

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


More information about the ghc-tickets mailing list