#5252: UNPACK without optimisation leads to panic
---------------------------------+------------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.0.3
Keywords: | Testcase:
Blockedby: | Difficulty:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
Here's a two-module progam
{{{
module Foo where
import Bar
blah :: S -> T
blah (MkS x _) = x
module Bar( S(..), T ) where
data T = MkT Int Int
data S = MkS {-# UNPACK #-}!T Int
}}}
Now with ghc 7.0.3 we get
{{{
bash-3.1$ ghc -c Bar.hs
bash-3.1$ ghc -c Foo.hs
ghc.exe: panic! (the 'impossible' happened)
(GHC version 7.0.3 for i386-unknown-mingw32):
reboxProduct: not a product main:Foo1.T{tc r2}
}}}
The problem is that
* We are compiling with -O so GHC tries to put as little as possible into
the interface file `Bar.hi`. And it does not put in T's constructors
{{{
data S
RecFlag NonRecursive
Generics: no
= MkS :: Foo1.T -> GHC.Types.Int -> S
HasWrapper
Stricts: {-# UNPACK #-} ! _
43edb8535d0555fb50e9f93a9c3203bf
data T
RecFlag NonRecursive
Generics: no
{- abstract -}
}}}
* However the pattern match in `Foo` requires that GHC can see the full
representation for T, becuase it UNPACK's the argument.
* A workaround is to export `MkT` from `Bar`.
The solution I am implementing is to ignore UNPACK pragmas when
`OmitInterfacePragmas` is on. This flag is the one that causes trimming
of the exposed constructors.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5252>
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