
#12968: GHC crash with TypeInType and pattern synonym -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I decided to try playing with the proposed new `Typeable` interface, faking up types and functions in GHC 8.0.1. Unfortunately, it seems I did something impossible: {{{#!hs {-# LANGUAGE TypeInType, GADTs, ScopedTypeVariables, PatternSynonyms, ViewPatterns #-} module TypeReflection where data TypeRep (a :: k) data TRAppG (fun :: k2) where TRAppG :: forall k1 (a :: k1 -> k2) (b :: k1) . TypeRep a -> TypeRep b -> TRAppG (a b) pattern TRApp :: forall k2 (fun :: k2). () => forall k1 (a :: k1 -> k2) (b :: k1). (fun ~ a b) => TypeRep a -> TypeRep b -> TypeRep fun pattern TRApp a b <- ((undefined :: TypeRep fun -> TRAppG fun) -> TRAppG a b) }}} The error: {{{ [1 of 1] Compiling TypeReflection ( TypeReflectionTemplate.hs, TypeReflectionTemplate.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): StgCmmEnv: variable not found $dIP_a1Aj local binds for: typeRep $tcTypeable $tc'C:Typeable $tcTypeRep $tc'TRAppG $WTRAppG $tcTRAppG $trModule $tcTRAppG1_r1KE $tc'TRAppG1_r1KS $tcTypeRep1_r1KT $tcTypeable1_r1KU $tc'C:Typeable1_r1KV $trModule1_r1KW $trModule2_r1KX scrut_s1Lg cont_s1Lh fail_s1Li sat_s1Lj sat_s1Lk sat_s1Ll sat_s1Lm sat_s1Ln sat_s1Lo sat_s1Lp sat_s1Lq sat_s1Lr sat_s1Ls sat_s1Lt }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12968 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler