[GHC] #13782: Bullish use of Template Haskell's newName causes GHC internal error

#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

#13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | 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: | -------------------------------------+------------------------------------- Changes (by dfeuer): * priority: normal => high * failure: GHC rejects valid program => Compile-time crash or panic * milestone: => 8.2.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13782#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #12503 Comment: As I thought, #12503 is very closely related to this ticket. Both this ticket and #12503 were caused by commit 6746549772c5cc0ac66c0fce562f297f4d4b80a2 (Add kind equalities to GHC). While this ticket concerns using a reified type variable in a function declaration, #12503 was about using a reified kind variable in an instance declaration. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13782#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: carlostome Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by carlostome): * owner: (none) => carlostome Comment: Looking into it at ZuriHac, we suspect the function dropWildCards is where the problem lies. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13782#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: carlostome Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by carlostome): After some debugging I found out that the bug arises in the following function from [https://git.haskell.org/ghc.git/blob/HEAD:/compiler/rename/RnTypes.hs#l1711 RnTypes] {{{ #!haskell extract_hs_tv_bndrs :: [LHsTyVarBndr GhcPs] -> FreeKiTyVars -> FreeKiTyVars -> RnM FreeKiTyVars -- In (forall (a :: Maybe e). a -> b) we have -- 'a' is bound by the forall -- 'b' is a free type variable -- 'e' is a free kind variable extract_hs_tv_bndrs tvs (FKTV acc_kvs acc_k_set acc_tvs acc_t_set acc_all) -- Note accumulator comes first (FKTV body_kvs body_k_set body_tvs body_t_set body_all) | null tvs = return $ FKTV (body_kvs ++ acc_kvs) (body_k_set `unionOccSets` acc_k_set) (body_tvs ++ acc_tvs) (body_t_set `unionOccSets` acc_t_set) (body_all ++ acc_all) | otherwise = do { FKTV bndr_kvs bndr_k_set _ _ _ <- foldrM extract_lkind emptyFKTV [k | L _ (KindedTyVar _ k) <- tvs] ; let locals = mkOccSet $ map (rdrNameOcc . hsLTyVarName) tvs ; return $ FKTV (filterOut ((`elemOccSet` locals) . rdrNameOcc . unLoc) (bndr_kvs ++ body_kvs) ++ acc_kvs) ((body_k_set `minusOccSet` locals) `unionOccSets` acc_k_set `unionOccSets` bndr_k_set) (filterOut ((`elemOccSet` locals) . rdrNameOcc . unLoc) body_tvs ++ acc_tvs) ((body_t_set `minusOccSet` locals) `unionOccSets` acc_t_set) (filterOut ((`elemOccSet` locals) . rdrNameOcc . unLoc) (bndr_kvs ++ body_all) ++ acc_all) } }}} In the case ''tvs'' is empty, the '''locals''' variable holds the set of OccName found in tvs. The OccName of variable ''a2'' in the program with the line: {{{#!haskell [f,a2] <- mapM newName ["f","a"] }}} is 'a' and thus the variable is filtered out from ''bndr_kvs ++ body_kvs'' (Which I guess holds the variable 'a' from ''data Maybe a''). However, in the program with the line: {{{#!haskell [f,a2] <- mapM newName ["f","b"] }}} the ''OccName'' of ''a2'' is "b" and doesn't get filtered out because it's OccName is not "a". In the previous version of the commit 6746549772c5cc0ac66c0fce562f297f4d4b80a2 that changed this function, the variables where filtered regarding the full name (Which in this case is a ''Exact'' name) not only its OccName and the problem didn't existed. I guess one way to solve this would be to filter out again based on full names and not only the ''OccName'' of variables. Any thoughts? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13782#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: carlostome Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Phab:D3641 Wiki Page: | -------------------------------------+------------------------------------- Changes (by carlostome): * differential: => Phab:D3641 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13782#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: carlostome Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * cc: goldfire (added) * differential: Phab:D3641 => Comment: Yes, I think you are right. For some undocumented reason, Richard, you changed this function to manipulate {{{ data FreeKiTyVars = FKTV { fktv_kis :: [Located RdrName] , _fktv_k_set :: OccSet -- for efficiency, -- only used internally , fktv_tys :: [Located RdrName] , _fktv_t_set :: OccSet , fktv_all :: [Located RdrName] } }}} instead of just the `fktv_kis` and `fktv_tys` pair which it used before. Moreover you switched to using `OccNames` for equality rather than `RdrNames`. Might you fix? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13782#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: carlostome Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Phab:D3641 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D3641 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13782#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: carlostome Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Phab:D3641 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I have [https://phabricator.haskell.org/D3641#103588 commented] on the Phab Diff. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13782#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: carlostome Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Phab:D3641 Wiki Page: | -------------------------------------+------------------------------------- Comment (by carlostome): The FreeKiTyVars datatype is local to the [https://git.haskell.org/ghc.git/blob/HEAD:/compiler/renamer/RnTypes.hs RnTypes] module, so I think the way to go is to change the [https://git.haskell.org/ghc.git/blob/HEAD:/compiler/basicTypes/OccName.hs#l4... OccSet] for a RdrSet (with the same API) and include this one on [https://git.haskell.org/ghc.git/blob/HEAD:/compiler/basicTypes/OccName.hs RdrName]. The only difficulty I find is to come up with a sensible Uniquable instance for RdrName. {{{ #!haskell instance Uniquable RdrName where getUnique (Exact name) = ... getUnique (Unqual occ) = ... getUnique (Qual mod occ) = ... getUnique (Orig mod occ) = ... }}} In the cases for '''Exact''' and '''Unqual''' we would like to tag the ''Unique'' of name and occ and for the cases of '''Qual''' and '''Orig''' to tag and combine somehow the Unques for mod and occ. How can we do this? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13782#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: carlostome Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Phab:D3641 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I agree with Richard's comment that the fix is suspicous. For now, let's just dump the `OccSets` entirely, and filter the `RdrName` lists. This will actually be more efficient in the common case of small sets. If we find programs with zillions of foralls we can deal with it then. Incidentally, even as it stands we call `nub` on these lists, and there is lots of appending, which is equally quadratic. I believe, but I am not sure, that `fkfv_all = fktv_kis ++ kktv_tys`. Assuming so, let's dump `fktv_all` too leaving only two fields, and just append when needed. Unless the ''order'' is significant? Nothing in the comments suggest that it is. Richard? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13782#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: carlostome Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Phab:D3641 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): A variable could conceivably be mentioned in both `ftkv_kis` and `ftkv_tys`, so naive appending might cause duplication. I don't think order is significant. If it turns out to be somewhere, we could always use the source locations to restore order. Agreed with Simon's plan in comment:10. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13782#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13782: Bullish use of Template Haskell's newName causes GHC internal error
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: carlostome
Type: bug | Status: patch
Priority: high | Milestone: 8.2.1
Component: Template Haskell | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: #12503 | Differential Rev(s): Phab:D3641
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: carlostome Type: bug | Status: merge Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Phab:D3641 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13782#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: carlostome Type: bug | Status: closed Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Phab:D3641 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged with 05ae09c7fac3e82a0b651980080fc472eb15e995. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13782#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC