
#13738: TypeApplications-related GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | TypeApplications 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: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): BTW, this is pretty much the exact code that GHC emits with `-ddump-deriv` if you try to write this `C (Wrap f)` instance with `GeneralizedNewtypeDeriving`: {{{#!hs {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE PolyKinds #-} {-# OPTIONS_GHC -ddump-deriv #-} module Works where newtype Wrap f a = Wrap (f a) deriving C class C f where c :: f a }}} {{{ GHCi, version 8.3.20170516: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Works ( Works.hs, interpreted ) ==================== Derived instances ==================== Derived class instances: instance forall k (f :: k -> *). Works.C f => Works.C (Works.Wrap f) where Works.c = GHC.Prim.coerce @(forall (a_a1tD :: k_a1uE). f_a1tE a_a1tD) @(forall (a_a1tD :: k_a1uE). Works.Wrap f_a1tE a_a1tD) Works.c Derived type family instances: }}} This reveals a pretty-printing bug, as the explicitly quantified kind variable `k` referred to by a different name `k_a1uE` later. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13738#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler