[GHC] #13837: Calling qReifyInstances on out-of-scope Name leads to GHC internal error
GHC
ghc-devs at haskell.org
Fri Jun 16 23:43:34 UTC 2017
#13837: Calling qReifyInstances on out-of-scope Name leads to 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: Compile-time
Unknown/Multiple | crash or panic
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
module Bug where
import Language.Haskell.TH.Lib
import Language.Haskell.TH.Syntax
test_local_tyfam_expansion :: String
test_local_tyfam_expansion =
$(do fam_name <- newName "Fam"
stringE . show =<< qReifyInstances fam_name [])
}}}
{{{
$ /opt/ghc/8.2.1/bin/ghci Bug2.hs
GHCi, version 8.2.0.20170523: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Bug ( Bug2.hs, interpreted )
Bug2.hs:9:5: error:
• The exact Name ‘Fam_a4pX’ is not in scope
Probable cause: you used a unique Template Haskell name (NameU),
perhaps via newName, but did not bind it
If that's it, then -ddump-splices might be useful
• In the argument of reifyInstances: Fam_0
In the untyped splice:
$(do fam_name <- newName "Fam"
stringE . show =<< qReifyInstances fam_name [])
|
9 | $(do fam_name <- newName "Fam"
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
Bug2.hs:9:5: error:
• GHC internal error: ‘Fam_a4pX’ is not in scope during type checking,
but it passed the renamer
tcl_env of environment: []
• In the type ‘Fam_a4pX’
In the argument of reifyInstances: Fam_0
In the untyped splice:
$(do fam_name <- newName "Fam"
stringE . show =<< qReifyInstances fam_name [])
|
9 | $(do fam_name <- newName "Fam"
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
}}}
This appears to have started happening in GHC 7.10, since with 7.8, you
only get this:
{{{
GHCi, version 7.8.4: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Bug ( Bug2.hs, interpreted )
Loading package array-0.5.0.0 ... linking ... done.
Loading package deepseq-1.3.0.2 ... linking ... done.
Loading package containers-0.5.5.1 ... linking ... done.
Loading package pretty-1.1.1.1 ... linking ... done.
Loading package template-haskell ... linking ... done.
Bug2.hs:9:5:
The exact Name ‘Fam_a2gK’ is not in scope
Probable cause: you used a unique Template Haskell name (NameU),
perhaps via newName, but did not bind it
If that's it, then -ddump-splices might be useful
In the argument of reifyInstances: Fam_0
In the splice:
$(do { fam_name <- newName "Fam";
stringE . show =<< qReifyInstances fam_name [] })
}}}
This problem appears to be somewhat specific to `qReifyInstances`, since
switching it out with `qReify` does not trigger the internal error:
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
module Bug where
import Language.Haskell.TH.Lib
import Language.Haskell.TH.Syntax
test_local_tyfam_expansion :: String
test_local_tyfam_expansion =
$(do fam_name <- newName "Fam"
stringE . show =<< qReify fam_name)
}}}
{{{
GHCi, version 8.2.0.20170523: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Bug ( Bug2.hs, interpreted )
Bug2.hs:9:5: error:
• The exact Name ‘Fam_a4od’ is not in scope
Probable cause: you used a unique Template Haskell name (NameU),
perhaps via newName, but did not bind it
If that's it, then -ddump-splices might be useful
• In the untyped splice:
$(do fam_name <- newName "Fam"
stringE . show =<< qReify fam_name)
|
9 | $(do fam_name <- newName "Fam"
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
Bug2.hs:9:5: error:
• The exact Name ‘Fam_a4od’ is not in scope
Probable cause: you used a unique Template Haskell name (NameU),
perhaps via newName, but did not bind it
If that's it, then -ddump-splices might be useful
• In the untyped splice:
$(do fam_name <- newName "Fam"
stringE . show =<< qReify fam_name)
|
9 | $(do fam_name <- newName "Fam"
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
Bug2.hs:9:5: error:
• ‘Fam_a4od’ is not in the type environment at a reify
• In the untyped splice:
$(do fam_name <- newName "Fam"
stringE . show =<< qReify fam_name)
|
9 | $(do fam_name <- newName "Fam"
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13837>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list