#3964: Impossible happened when using ViewPattern in Arrows
-------------------------------+--------------------------------------------
Reporter: uzytkownik | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 6.12.1 | Keywords:
Os: Linux | Testcase:
Architecture: x86_64 (amd64) | Failure: Compile-time crash
-------------------------------+--------------------------------------------
Comment(by uzytkownik):
Even more simplifized example:
{{{
{-# LANGUAGE Arrows #-}
{-# LANGUAGE ViewPatterns #-}
import Control.Arrow
testF :: Eq a => a -> (Maybe (Maybe a)) -> Maybe a
testF v = proc x -> case x of
Just (Just ((==v) -> True)) -> returnA -< Just v
_ -> returnA -< Nothing
}}}
{{{
ghc: panic! (the 'impossible' happened)
(GHC version 6.12.1 for x86_64-unknown-linux):
collectl/go
((=={v agq} [lid]
v{v afv} [lid]) -> {8:25-28}{8:25-28}ghc-prim:GHC.Bool.True{(w) d
6u})
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3964#comment:3>
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