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

#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

#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 Resolution: | 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: | ---------------------------------+---------------------------------------- Comment (by simonpj): While I have not reproduced this, it looks like a dup of #10045. Can you try with HEAD? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11059#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Resolution: | 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: | ---------------------------------+---------------------------------------- Comment (by dimitri-xyz): I'm a newbie here. I don't know what is required to build HEAD, but I'll try to build it this weekend and update here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11059#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Resolution: | 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: | ---------------------------------+---------------------------------------- Comment (by goldfire): We generally prefer if you can reproduce the bug without external libraries. In this case, not only do you use `pipes` and `fingertree`, but you also use `pipes-concurrency`. The latter, sadly, does not build with HEAD because it depends on `stm`, which doesn't build. So I've tried testing this and failed, but you will too, with the exact same problem. Can you simplify your test case to remove the dependencies? If there are no packages used, it's much much easier for us to test. Thanks! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11059#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Resolution: | 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: | ---------------------------------+---------------------------------------- Comment (by svenpanne): #10967 ;-) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11059#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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
participants (1)
-
GHC