[GHC] #15783: Quoting an internal variable causes an error when splicing

#15783: Quoting an internal variable causes an error when splicing -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{ {-# LANGUAGE TemplateHaskell #-} module A where import B main = $$f }}} {{{ {-# LANGUAGE TemplateHaskell #-} module B(f) where d = 0 f = [|| d ||] }}} Note that `d` is not exported from `B`. {{{ [1 of 2] Compiling B ( B.hs, B.o ) [2 of 2] Compiling A ( A.hs, A.o ) A.hs:6:8: error: • Can't find interface-file declaration for variable B.d Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error • In the expression: B.d In the result of the splice: $f To see what the splice expanded to, use -ddump-splices In the Template Haskell splice $$f | 6 | main = $$f | ^^^ }}} This doesn't seem to happen for untyped quotes/splices. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15783 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15783: Quoting an internal variable causes an error when splicing -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) * component: Compiler => Template Haskell -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15783#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15783: Quoting an internal variable causes an error when splicing -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Curiously, this doesn't happen when loaded into GHCi, only when compiled with `--make`. Also, if you compile these files one at a time with `-c`, you get something... interesting: {{{ $ /opt/ghc/8.6.1/bin/ghc -c B.hs $ /opt/ghc/8.6.1/bin/ghc -c A.hs ghc: panic! (the 'impossible' happened) (GHC version 8.6.1 for x86_64-unknown-linux): Loading temp shared object failed: /tmp/ghc6527_0/libghc_1.so: undefined symbol: templatezmhaskell_LanguageziHaskellziTHziLib_varE_closure }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15783#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15783: Quoting an internal variable causes an error when splicing -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Another curious thing. If you compile `B.hs` with `-ddump-simpl`, you'll get this: {{{ $ /opt/ghc/8.6.1/bin/ghc B.hs -fforce-recomp -ddump-simpl [1 of 1] Compiling B ( B.hs, B.o ) ==================== Tidy Core ==================== Result size of Tidy Core = {terms: 24, types: 9, coercions: 0, joins: 0/0} -- RHS size: {terms: 9, types: 1, coercions: 0, joins: 0/0} f :: Language.Haskell.TH.Syntax.Q (Language.Haskell.TH.Syntax.TExp Integer) [GblId] f = Language.Haskell.TH.Syntax.unsafeTExpCoerce @ Integer (Language.Haskell.TH.Lib.Internal.varE (Language.Haskell.TH.Syntax.mkNameG_v (GHC.CString.unpackCString# "main"#) (GHC.CString.unpackCString# "B"#) (GHC.CString.unpackCString# "d"#))) <Typeable stuff elided> }}} Now change the typed quote to an untyped one (i.e., change `f = [|| d ||]` to `f = [| d |]`) and recompile it: {{{ $ /opt/ghc/8.6.1/bin/ghc B.hs -fforce-recomp -ddump-simpl [1 of 1] Compiling B ( B.hs, B.o ) ==================== Tidy Core ==================== Result size of Tidy Core = {terms: 25, types: 7, coercions: 0, joins: 0/0} -- RHS size: {terms: 8, types: 0, coercions: 0, joins: 0/0} f :: Language.Haskell.TH.Lib.Internal.ExpQ [GblId] f = Language.Haskell.TH.Lib.Internal.varE (Language.Haskell.TH.Syntax.mkNameG_v (GHC.CString.unpackCString# "main"#) (GHC.CString.unpackCString# "B"#) (GHC.CString.unpackCString# "d"#)) -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} d :: Integer [GblId, Caf=NoCafRefs, Unf=OtherCon []] d = 0 <Typeable stuff elided> }}} Notice that `d` actually makes an appearance this time! This makes me wonder if `d` is being mistakenly removed under the pretense of it being dead code. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15783#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15783: Quoting an internal variable causes an error when splicing -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5248 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D5248 Comment: I figured out what's causing this. See Phab:D5248 for a fix. It turns out that occurrence analysis was dropping the binding for `d` during desugaring (this explains why this bug didn't surface in GHCi, as occurrence analysis does not run there). So why was occurrence analysis dropping bindings for top-level things referenced from typed TH quotes, but not from untyped TH quotes? It turns out that two functions called `checkCrossStageLifting` are to blame. ...No seriously, there are two completely separate functions named `checkCrossStageLifting` in GHC. One exists in `RnSplice`, and only handles untyped quotes, and the other exists in `TcExpr`, and only handles typed quotes. And wouldn't you know it, `RnSplice.checkCrossStageLifting` was doing something that `TcExpr.checkCrossStageLifting` wasn't doing. In particular, [http://git.haskell.org/ghc.git/blob/879db5595208fb665ff1a0a2b12b9921d3efae0e... these lines] of `RnSplice.checkCrossStageLifting` are crucial: {{{#!hs | isTopLevel top_lvl -- Top-level identifiers in this module, -- (which have External Names) -- are just like the imported case: -- no need for the 'lifting' treatment -- E.g. this is fine: -- f x = x -- g y = [| f 3 |] = when (isExternalName name) (keepAlive name) -- See Note [Keeping things alive for Template Haskell] }}} That call to `keepAlive` ensures that the binding for `f` (from the example in the comments) doesn't get discarded during occurrence analysis. `TcExpr.checkCrossStageLifting` wasn't doing anything like this, which explains why this bug exists. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15783#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15783: Quoting an internal variable causes an error when splicing
-------------------------------------+-------------------------------------
Reporter: mpickering | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Template Haskell | Version: 8.6.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D5248
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#15783: Quoting an internal variable causes an error when splicing -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.8.1 Component: Template Haskell | Version: 8.6.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: th/T15783 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5248 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => closed * testcase: => th/T15783 * resolution: => fixed * milestone: => 8.8.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15783#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC