[GHC] #12401: GHC panic! Template variable unbound in rewrite rule
GHC
ghc-devs at haskell.org
Sat Jul 16 17:23:58 UTC 2016
#12401: GHC panic! Template variable unbound in rewrite rule
-------------------------------------+-------------------------------------
Reporter: vagarenko | Owner:
Type: bug | Status: new
Priority: high | Milestone:
Component: Compiler | Version: 8.0.1
Keywords: | Operating System: Windows
Architecture: x86_64 | Type of failure: Compile-time
(amd64) | crash
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
When compiling following code with `-O`:
{{{#!hs
{-# LANGUAGE FlexibleContexts, TypeFamilies, TypeSynonymInstances #-}
module Bug where
import Data.Word
import Foreign.Storable
import qualified Data.Vector.Storable as VS
data Image a = Image
{ imageWidth :: !Int
, imageHeight :: !Int
, imageData :: VS.Vector (PixelBaseComponent a)
}
class (Storable (PixelBaseComponent a)) => Pixel a where
type PixelBaseComponent a :: *
instance Pixel Pixel8 where type PixelBaseComponent Pixel8 = Word8
instance Pixel Pixel16 where type PixelBaseComponent Pixel16 = Word16
data DynamicImage =
ImageY8 (Image Pixel8)
| ImageY16 (Image Pixel16)
type Pixel8 = Word8
type Pixel16 = Word16
-- |
imageMirrorY :: DynamicImage -> DynamicImage
imageMirrorY dynImg = case dynImg of
ImageY8 img -> ImageY8 $ mirror img 1
ImageY16 img -> ImageY16 $ mirror img 1
where
mirror img channels = img { imageData = VS.concat $ reverse $ map
(\y -> VS.slice (y * rowLen) rowLen (imageData img)) [0 .. imageHeight img
- 1] }
where
rowLen = channels * imageWidth img
}}}
I get error:
{{{
> ghc Bug -O
[1 of 1] Compiling Bug ( Bug.hs, Bug.o )
ghc: panic! (the 'impossible' happened)
(GHC version 8.0.1 for x86_64-unknown-mingw32):
Template variable unbound in rewrite rule
Variable: cobox_s5Rv
Rule "SPEC mirror @ Pixel8 @ Pixel8"
Rule bndrs: [cobox_s5Rv, $dStorable_s5Rw]
LHS args: [TYPE: Pixel8, TYPE: Pixel8,
CO: <PixelBaseComponent Pixel8>_N, $dStorable_s5Rw]
Actual args: [TYPE: Pixel8, TYPE: Pixel8,
CO: <PixelBaseComponent Pixel8>_N,
$fStorableWord8
`cast` ((Storable (Sym D:R:PixelBaseComponentWord8[0]))_R
:: (Storable Word8 :: Constraint)
~R#
(Storable (PixelBaseComponent Pixel8) ::
Constraint)),
img_a4IS, lvl_s7o4]
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12401>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list