
#13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.0.1 Haskell | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- int-index originally spotted this bug at https://github.com/goldfirere/singletons/issues/150#issuecomment-305909199. To reproduce, compile this file with GHC 8.0.1, 8.0.2, 8.2.1, or HEAD: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TemplateHaskell #-} module Bug where import Language.Haskell.TH $(do TyConI (DataD _ _ [KindedTV a1 _] _ _ _) <- reify ''Maybe [f,a2] <- mapM newName ["f","a"] return [ SigD f (ForallT [KindedTV a2 (AppT (ConT ''Maybe) (VarT a1))] [] (ConT ''Int)) , ValD (VarP f) (NormalB (LitE (IntegerL 42))) [] ]) }}} {{{ GHCi, version 8.2.0.20170522: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:9:3: error: • GHC internal error: ‘a_11’ is not in scope during type checking, but it passed the renamer tcl_env of environment: [] • In the first argument of ‘Maybe’, namely ‘a_11’ In the kind ‘Maybe a_11’ In the type signature: f :: forall (a_a4Qz :: Maybe a_11). Int | 9 | $(do TyConI (DataD _ _ [KindedTV a1 _] _ _ _) <- reify ''Maybe | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^... }}} The root cause of the issue seems to be that the name `a` (which we picked for `newName`) happens to clash with the type variable we reified from `Maybe` (since `data Maybe a = ...`). If we pick a different name: {{{#!hs [f,a2] <- mapM newName ["f","albatross"] }}} Then it will compile. This is a regression from GHC 7.10.3, as it compiles in that version (with a slight change to accommodate the API differences in `DataD` between 7.10.3 and 8.0): {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TemplateHaskell #-} module Works where import Language.Haskell.TH $(do TyConI (DataD _ _ [KindedTV a1 _] _ _) <- reify ''Maybe [f,a2] <- mapM newName ["f","a"] return [ SigD f (ForallT [KindedTV a2 (AppT (ConT ''Maybe) (VarT a1))] [] (ConT ''Int)) , ValD (VarP f) (NormalB (LitE (IntegerL 42))) [] ]) }}} {{{ $ /opt/ghc/7.10.3/bin/ghci Works.hs -ddump-splices GHCi, version 7.10.3: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Works ( Works.hs, interpreted ) Works.hs:(9,3)-(14,13): Splicing declarations do { TyConI (DataD _ _ [KindedTV a1_a3jt _] _ _) <- reify ''Maybe; [f_a3nh, a2_a3ni] <- mapM newName ["f", "a"]; return [SigD f_a3nh (ForallT [KindedTV a2_a3ni (AppT (ConT ''Maybe) (VarT a1_a3jt))] [] (ConT ''Int)), ValD (VarP f_a3nh) (NormalB (LitE (IntegerL 42))) []] } ======> f_a4vc :: forall (a_a4vd :: Maybe a_a4v3). Int f_a4vc = 42 Ok, modules loaded: Works. }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13782 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler