[GHC] #7887: panic when playing with pipes

#7887: panic when playing with pipes -----------------------------+---------------------------------------------- Reporter: bfr | Owner: Type: bug | Status: new Priority: normal | Component: Compiler Version: 7.6.3 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: -----------------------------+---------------------------------------------- I am playing around with pipes-3.2.0 using ghc-6.7.3. I load this code in ghci: """ import Control.Proxy fork :: (Monad m, Proxy p1, Proxy p2, Proxy p3) => () -> Consumer p1 a (Producer p2 a (Producer p3 a m)) r fork () = runIdentityP . hoist (runIdentityP . hoist runIdentityP) $ forever $ do a <- request () -- Request from the 'Consumer' lift $ respond a -- Send to the outer 'Producer' lift $ lift $ respond a -- Send to the inner 'Producer' test :: (Proxy p) => () -> Producer p Int IO r test () = runIdentityP $ forever $ do respond 1 """ then I type *Main> :t hoist (hoist lift) $ test <interactive>:1:1: Warning: Could not deduce (Monad ()) arising from a use of `hoist' from the context (Monad m, MonadTrans t1, Proxy p, MFunctor t) bound by the inferred type of it :: (Monad m, MonadTrans t1, Proxy p, MFunctor t) => t (t1 m) -> Producer p Int IO r at Top level Possible fix: add an instance declaration for (Monad ()) In the expression: hoist (hoist lift) In the expression: hoist (hoist lift) $ test <interactive>:1:1: Warning: Could not deduce (MFunctor (->)) arising from a use of `hoist' from the context (Monad m, MonadTrans t1, Proxy p, MFunctor t) bound by the inferred type of it :: (Monad m, MonadTrans t1, Proxy p, MFunctor t) => t (t1 m) -> Producer p Int IO r at Top level Possible fix: add an instance declaration for (MFunctor (->)) In the expression: hoist (hoist lift) In the expression: hoist (hoist lift) $ test <interactive>:1:8: Warning:ghc: panic! (the 'impossible' happened) (GHC version 7.6.3 for x86_64-unknown-linux): kindFunResult <<details unavailable>> Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7887 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7887: panic when playing with pipes -----------------------------+---------------------------------------------- Reporter: bfr | Owner: Type: bug | Status: new Priority: normal | Component: Compiler Version: 7.6.3 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: -----------------------------+---------------------------------------------- Comment(by bfr): Oops, my code was garbled, please see attached file for correctly formatted code. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7887#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7887: panic when playing with pipes -----------------------------+---------------------------------------------- Reporter: bfr | Owner: Type: bug | Status: new Priority: normal | Component: Compiler Version: 7.6.3 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: -----------------------------+---------------------------------------------- Comment(by bfr): Note: I used -f-defer-type-errors, but the bug happens without that flag, too (and without the two type warnings). -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7887#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7887: panic when playing with pipes ---------------------------------+------------------------------------------ Reporter: bfr | Owner: Type: bug | Status: closed Priority: normal | Component: Compiler Version: 7.6.3 | Resolution: fixed Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Blockedby: | Blocking: Related: | ---------------------------------+------------------------------------------ Changes (by monoidal): * status: new => closed * resolution: => fixed Comment: It's fixed in HEAD. Here's a stripped version without dependency on pipes: {{{ {-# LANGUAGE RankNTypes #-} hoist :: (forall a. m a -> n a) -> t m b -> t n b hoist = hoist test :: () -> a test = test lift :: m a -> t m a lift = lift x = hoist (hoist lift) test }}} 7.6 panicks, but HEAD gives {{{ C.hs:12:24: Couldn't match type ‛t1 m’ with ‛()’ Expected type: t (t1 m) a Actual type: () -> a Relevant bindings include x :: t (t1 (t2 m)) a (bound at C.hs:12:1) In the second argument of ‛hoist’, namely ‛test’ In the expression: hoist (hoist lift) test }}} which is a correct error. (I opened #7888 as a leftover of debugging.) -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7887#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7887: panic when playing with pipes ---------------------------------+------------------------------------------ Reporter: bfr | Owner: Type: bug | Status: closed Priority: normal | Component: Compiler Version: 7.6.3 | Resolution: fixed Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Blockedby: | Blocking: Related: | ---------------------------------+------------------------------------------ Comment(by bfr): Thanks, I am glad it's been fixed. Is there a chance the fix will be backported to the STABLE branch (i.e. 6.7.x)? -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7887#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7887: panic when playing with pipes -------------------------------+-------------------------------------------- Reporter: bfr | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: fixed | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: | Related: -------------------------------+-------------------------------------------- Changes (by igloo): * difficulty: => Unknown Old description:
I am playing around with pipes-3.2.0 using ghc-6.7.3. I load this code in ghci:
""" import Control.Proxy
fork :: (Monad m, Proxy p1, Proxy p2, Proxy p3) => () -> Consumer p1 a (Producer p2 a (Producer p3 a m)) r fork () = runIdentityP . hoist (runIdentityP . hoist runIdentityP) $ forever $ do a <- request () -- Request from the 'Consumer' lift $ respond a -- Send to the outer 'Producer' lift $ lift $ respond a -- Send to the inner 'Producer'
test :: (Proxy p) => () -> Producer p Int IO r test () = runIdentityP $ forever $ do respond 1 """
then I type
*Main> :t hoist (hoist lift) $ test
<interactive>:1:1: Warning: Could not deduce (Monad ()) arising from a use of `hoist' from the context (Monad m, MonadTrans t1, Proxy p, MFunctor t) bound by the inferred type of it :: (Monad m, MonadTrans t1, Proxy p, MFunctor t) => t (t1 m) -> Producer p Int IO r at Top level Possible fix: add an instance declaration for (Monad ()) In the expression: hoist (hoist lift) In the expression: hoist (hoist lift) $ test
<interactive>:1:1: Warning: Could not deduce (MFunctor (->)) arising from a use of `hoist' from the context (Monad m, MonadTrans t1, Proxy p, MFunctor t) bound by the inferred type of it :: (Monad m, MonadTrans t1, Proxy p, MFunctor t) => t (t1 m) -> Producer p Int IO r at Top level Possible fix: add an instance declaration for (MFunctor (->)) In the expression: hoist (hoist lift) In the expression: hoist (hoist lift) $ test
<interactive>:1:8: Warning:ghc: panic! (the 'impossible' happened) (GHC version 7.6.3 for x86_64-unknown-linux): kindFunResult <<details unavailable>>
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
New description: I am playing around with pipes-3.2.0 using ghc-6.7.3. I load this code in ghci: {{{ import Control.Proxy fork :: (Monad m, Proxy p1, Proxy p2, Proxy p3) => () -> Consumer p1 a (Producer p2 a (Producer p3 a m)) r fork () = runIdentityP . hoist (runIdentityP . hoist runIdentityP) $ forever $ do a <- request () -- Request from the 'Consumer' lift $ respond a -- Send to the outer 'Producer' lift $ lift $ respond a -- Send to the inner 'Producer' test :: (Proxy p) => () -> Producer p Int IO r test () = runIdentityP $ forever $ do respond 1 }}} then I type {{{ *Main> :t hoist (hoist lift) $ test <interactive>:1:1: Warning: Could not deduce (Monad ()) arising from a use of `hoist' from the context (Monad m, MonadTrans t1, Proxy p, MFunctor t) bound by the inferred type of it :: (Monad m, MonadTrans t1, Proxy p, MFunctor t) => t (t1 m) -> Producer p Int IO r at Top level Possible fix: add an instance declaration for (Monad ()) In the expression: hoist (hoist lift) In the expression: hoist (hoist lift) $ test <interactive>:1:1: Warning: Could not deduce (MFunctor (->)) arising from a use of `hoist' from the context (Monad m, MonadTrans t1, Proxy p, MFunctor t) bound by the inferred type of it :: (Monad m, MonadTrans t1, Proxy p, MFunctor t) => t (t1 m) -> Producer p Int IO r at Top level Possible fix: add an instance declaration for (MFunctor (->)) In the expression: hoist (hoist lift) In the expression: hoist (hoist lift) $ test <interactive>:1:8: Warning:ghc: panic! (the 'impossible' happened) (GHC version 7.6.3 for x86_64-unknown-linux): kindFunResult <<details unavailable>> Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7887#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7887: panic when playing with pipes -------------------------------+-------------------------------------------- Reporter: bfr | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: fixed | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: | Related: -------------------------------+-------------------------------------------- Comment(by igloo): It's very unlikely we'll make another 7.6.x release. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7887#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC