#5045: "panic! (the 'impossible' happened)" compiling code using arrows and
elimReader (test case included)
-------------------------------+--------------------------------------------
Reporter: josh | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.0.2 | Keywords:
Testcase: | Blockedby:
Os: Linux | Blocking:
Architecture: x86_64 (amd64) | Failure: None/Unknown
-------------------------------+--------------------------------------------
In trying to debug a different issue, I ran ghci on one of the modules in
Serialist, and encountered a ghc panic. I managed to reduce it down to
the following minimal test case:
{{{
{-# LANGUAGE Arrows #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RecordWildCards #-}
import Control.Arrow
import Control.Arrow.Transformer.Reader
newtype ByteString = FakeByteString String
pathInfo :: Monad m => m String
pathInfo = undefined
requestMethod :: Monad m => m String
requestMethod = undefined
getInputsFPS :: Monad m => m [(String, ByteString)]
getInputsFPS = undefined
class HTTPRequest r s | r -> s where
httpGetPath :: r -> String
httpSetPath :: r -> String -> r
httpGetMethod :: r -> String
httpGetInputs :: r -> [(String, s)]
data CGIDispatch = CGIDispatch {
dispatchPath :: String,
dispatchMethod :: String,
dispatchInputs :: [(String, ByteString)]
}
instance HTTPRequest CGIDispatch ByteString where
httpGetPath = dispatchPath
httpSetPath r s = r { dispatchPath = s }
httpGetMethod = dispatchMethod
httpGetInputs = dispatchInputs
runDispatch :: (Arrow a, ArrowAddReader CGIDispatch a a', Monad m) => a b
c -> m (a' b c)
runDispatch a = do
dispatchPath <- pathInfo
dispatchMethod <- requestMethod
dispatchInputs <- getInputsFPS
return $ proc b -> (| elimReader (a -< b) |) CGIDispatch { .. }
}}}
Running "ghci TestCase.hs" produces this panic:
{{{
GHCi, version 7.0.2: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Main ( TestCase.hs, interpreted )
ghc: panic! (the 'impossible' happened)
(GHC version 7.0.2 for x86_64-unknown-linux):
addTickHsExpr
(|/\(@ a{tv av7} [sk]).
((arrows-0.4.4.0:Control.Arrow.Internals.elimReader{v rg4}
[gid[ClassOp]])
@ main:Main.CGIDispatch{tc rot}
@ a{tv auK} [sk]
@ a'{tv auL} [sk]
$dArrowAddReader{v ava} [lid])
@ a{tv av7} [sk]
@ c{tv auO} [sk]
((a{v ap8} [lid] -< b{v apc} [lid]))|)
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
>
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5045>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs