[GHC] #12401: GHC panic! Template variable unbound in rewrite rule

#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

#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 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by vagarenko): If I provide type signature for `mirror`: {{{#!hs mirror :: (Storable (PixelBaseComponent a)) => Image a -> Int -> Image a }}} it compiles fine. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12401#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12401: GHC panic! Template variable unbound in rewrite rule -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | 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: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 8.0.2 Comment: Thanks for the rather minimal testcase. It can be minimized a bit further by eliminating the `Pixel{8,16}` synonyms with the RHSs. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12401#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12401: GHC panic! Template variable unbound in rewrite rule -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: Type: bug | Status: merge Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | 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: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge Comment: I think this is a dup of #12212. Certianly it works with HEAD. The fix for #12212 has been merged to the 8.0 branch, I think. I have not checked that it works with the 8.0 branch. I'll set status to 'merge' just to invite someone to test that. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12401#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12401: GHC panic! Template variable unbound in rewrite rule -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: fixed | 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: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Indeed this appears to be fixed in `ghc-8.0`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12401#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC