GHC panic with small TH code
[verdelyi@localhost CompilerGenerator-Haskell]$ cat BUG.hs
{-# LANGUAGE TemplateHaskell, TypeFamilies, RankNTypes, FlexibleContexts #-}
import Language.Haskell.TH
astTest :: Q [Dec]
astTest = [d|
generateWalker :: forall t . [t] -> [t]
generateWalker = id
class (Num (From t), Num (To t)) => TransformationPhase t where
type From t
type To t
type Downwards t
type Upwards t
executeTransformationPhase :: [t] -> [t]
executeTransformationPhase = undefined
|]
[verdelyi@localhost CompilerGenerator-Haskell]$ ghci BUG.hs
GHCi, version 6.12.2: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
[1 of 1] Compiling Main ( BUG.hs, interpreted )
ghc: panic! (the 'impossible' happened)
(GHC version 6.12.2 for i386-unknown-linux):
nameModule executeTransformationPhase{v agj}
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
>
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information