#3275: ghc: panic! (the 'impossible' happened)
-------------------------+--------------------------------------------------
Reporter: EricKow | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 6.10.4
Component: Compiler | Version: 6.10.3
Severity: normal | Resolution:
Keywords: | Difficulty: Unknown
Testcase: | Os: MacOS X
Architecture: x86 |
-------------------------+--------------------------------------------------
Comment (by igloo):
Great stuff, thanks Eric! I can now reproduce this:
{{{
{-# OPTIONS_GHC -O2 #-}
module Foo where
import Text.Regex
isJust :: Maybe a -> Bool
isJust (Just _) = True
isJust Nothing = False
foo :: IO (FilePath -> FilePath)
foo = do
regexes <- return undefined
let isbin f = or $ map (\r -> isJust $ matchRegex r f) regexes
ftf f = if isbin f then undefined else undefined
return ftf
}}}
{{{
$ ghc --make q
[1 of 1] Compiling Foo ( q.hs, q.o )
ghc: panic! (the 'impossible' happened)
(GHC version 6.10.3 for i386-apple-darwin):
cat_evals
base:GHC.Arr.Array{d rfk}
[ww{v aLo} [lid], ww1{v aLp} [lid], ww2{v aLq} [lid]]
[!, !, _, _]
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}}
It looks like despite the installer failing, I'm still getting `regex-
compat` from `/Library/Frameworks/HaskellPlatform.framework`. There is
also a copy in `/Library/Frameworks/GHC.framework`.
Core lint says:
{{{
$ ghc --make q -dcore-lint
[1 of 1] Compiling Foo ( q.hs, q.o )
ghc: panic! (the 'impossible' happened)
(GHC version 6.10.3 for i386-apple-darwin):
Iface Lint failure
Unfolding of regex-compat-0.71.0.1:Text.Regex.matchRegex{v r3n}
<no location info>:
In a case alternative: (base:Data.Maybe.Nothing{d r8})
In a case alternative, data constructor isn't in scrutinee type:
Scrutinee type constructor: ghc-prim:GHC.Types.[]{(w) tc 317}
Data con: base:Data.Maybe.Nothing{d r8}
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}}
In
{{{
ghc --show-iface /Library/Frameworks/HaskellPlatform.framework/lib/regex-
compat-0.71.0.1/ghc-6.10.3/Text/Regex.hi
}}}
is
{{{
3170b173e0108c4d0f4e4a6c458e962b
matchRegex :: Text.Regex.Posix.Wrap.Regex
-> GHC.Base.String
-> Data.Maybe.Maybe [GHC.Base.String]
{- Arity: 2 Strictness: LL
Unfolding: (\ p :: Text.Regex.Posix.Wrap.Regex
str :: GHC.Base.String ->
case @ (Data.Maybe.Maybe
[GHC.Base.String])
Text.Regex.Posix.String.a4 p str of wild {
Data.Maybe.Nothing -> Data.Maybe.Nothing @
[GHC.Base.String]
Data.Maybe.Just preMApost
-> Data.Maybe.Just
@ [GHC.Base.String]
(case @ [[GHC.Types.Char]] preMApost of w { (ww,
ww1, ww2) ->
case @ [[GHC.Types.Char]]
Text.Regex.Base.Context.$wlvl3
@ [GHC.Types.Char]
ww
ww1
ww2 of ww3 { (#
ww4, ww5, ww6, ww7 #) ->
ww7 } }) }) -}
5497cf2d6b99de31ced55bda7d2a1265
}}}
In
{{{
ghc --show-iface /Library/Frameworks/HaskellPlatform.framework/lib/regex-
posix-0.72.0.3/ghc-6.10.3/Text/Regex/Posix/String.hi
}}}
is
{{{
270f3a6a066ef52e8035aeae31f61c08
a4 :: Text.Regex.Posix.Wrap.Regex
-> GHC.Base.String
-> [Text.Regex.Base.RegexLike.MatchText GHC.Base.String]
{- Arity: 2 Strictness: LL -}
cd1e8839869c9407d5b2d1f9af8a4d06
}}}
In
{{{
ghc --show-iface
/Library/Frameworks/GHC.framework/Versions/610/usr/lib/ghc-6.10.3/regex-
posix-0.72.0.3/Text/Regex/Posix/String.hi
}}}
is
{{{
340c19d7034daffc230c61fd7b7524a7
a4 :: Text.Regex.Posix.Wrap.Regex
-> GHC.Base.String
-> Data.Maybe.Maybe
(GHC.Base.String,
Text.Regex.Base.RegexLike.MatchText GHC.Base.String,
GHC.Base.String)
{- Arity: 2 Strictness: LL -}
57f7a827fcdc372c03316de2b8a05865
}}}
so it looks like the problem is that `regex-compat` got built against the
`regex-posix` that comes with GHC rather than the one that comes with the
Haskell platform.
So, two questions:
Why did this happen?
Isn't the fingerprinting meant to catch this?
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3275#comment:7>
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