[GHC] #13587: addTopDecls fails with typed Template Haskell

#13587: addTopDecls fails with typed Template Haskell -------------------------------------+------------------------------------- Reporter: tmcdonell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.2.1-rc1 Haskell | 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: -------------------------------------+------------------------------------- The following untyped Template Haskell works as expected: {{{#!hs --- AddTopDecls.hs --- {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE QuasiQuotes #-} module AddTopDecls where import Language.Haskell.TH import Language.Haskell.TH.Syntax importDoubleToDouble :: String -> ExpQ importDoubleToDouble fname = do n <- newName fname d <- forImpD CCall unsafe fname n [t|Double -> Double|] addTopDecls [d] varE n --- Main.hs --- {-# LANGUAGE TemplateHaskell #-} module Main where import AddTopDecls main :: IO () main = do let sin' = $(importDoubleToDouble "sin") cos' = $(importDoubleToDouble "cos") -- print (sin' 0) print (cos' pi) }}} However it fails if I convert to the equivalent typed version: {{{#!hs --- AddTopDecls.hs --- {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE QuasiQuotes #-} module AddTopDecls where import Language.Haskell.TH import Language.Haskell.TH.Syntax importDoubleToDouble :: String -> Q (TExp (Double -> Double)) importDoubleToDouble fname = do n <- newName fname d <- forImpD CCall unsafe fname n [t|Double -> Double|] addTopDecls [d] unsafeTExpCoerce (varE n) --- Main.hs --- {-# LANGUAGE TemplateHaskell #-} module Main where import AddTopDecls main :: IO () main = do let sin' = $$(importDoubleToDouble "sin") cos' = $$(importDoubleToDouble "cos") -- print (sin' 0) print (cos' pi) }}} With the error: {{{
ghci Main.hs -ddump-splices GHCi, version 8.2.0.20170404: http://www.haskell.org/ghc/ :? for help [1 of 2] Compiling AddTopDecls ( AddTopDecls.hs, interpreted ) [2 of 2] Compiling Main ( Main.hs, interpreted ) Main.hs:9:19-44: Splicing expression importDoubleToDouble "sin" ======> sin_a4s2 Main.hs:1:1: Splicing top-level declarations added with addTopDecls ======> foreign import ccall unsafe "sin" Main.sin :: Double -> Double
Main.hs:9:19: error: • GHC internal error: ‘sin_a4s2’ is not in scope during type checking, but it passed the renamer tcl_env of environment: [a4dl :-> Identifier[sin'::t1, TopLevelLet [] False], a4dm :-> Identifier[cos'::t1, TopLevelLet [] False], r4cW :-> Identifier[main::IO (), TopLevelLet]] • In the expression: sin_a4s2 In the result of the splice: $importDoubleToDouble "sin" To see what the splice expanded to, use -ddump-splices In the Template Haskell splice $$(importDoubleToDouble "sin") | 9 | let sin' = $$(importDoubleToDouble "sin") | ^^^^^^^^^^^^^^^^^^^^^^^^^^ }}} Tested with 7.10.3, 8.0.2, and 8.2.0-rc1. Unfortunately I can't use untyped TH in my real use case, so if you have any suggestions for a workaround that would also be great. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13587 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13587: addTopDecls fails with typed Template Haskell -------------------------------------+------------------------------------- Reporter: tmcdonell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.1-rc1 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 goldfire): I'm the TH czar these days, but I'm swamped and won't be able to look at this until the end of the semester -- which is only two weeks away, thankfully. But if someone else can take a peek, that would be great! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13587#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13587: addTopDecls fails with typed Template Haskell -------------------------------------+------------------------------------- Reporter: tmcdonell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.1-rc1 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 erikd): I've just confirmed this in git HEAD (21c35bda8e). Even pulling `sin'` and `cos'` out to the top level and giving them explicit type signatures doesn't help. {{{ • GHC internal error: ‘cos_a4gy’ is not in scope during type checking, but it passed the renamer tcl_env of environment: [r34Z :-> Identifier[sin'::Double -> Double, TopLevelLet], r372 :-> Identifier[cos'::Double -> Double, TopLevelLet], r373 :-> Identifier[main::IO (), TopLevelLet]] • In the expression: cos_a4gy In the result of the splice: $importDoubleToDouble "cos" To see what the splice expanded to, use -ddump-splices In the Template Haskell splice $$(importDoubleToDouble "cos") }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13587#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13587: addTopDecls fails with typed Template Haskell -------------------------------------+------------------------------------- Reporter: tmcdonell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.1-rc1 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 erikd): The `-ddump-splices` output is: {{{ main.hs:11:11-36: Splicing expression importDoubleToDouble "cos" ======> cos_a4gy main.hs:1:1: Splicing top-level declarations added with addTopDecls ======> foreign import ccall unsafe "cos" Main.cos :: Double -> Double }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13587#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13587: addTopDecls fails with typed Template Haskell -------------------------------------+------------------------------------- Reporter: tmcdonell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.1-rc1 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 erikd): The `-ddump-rn` output is: {{{ ==================== Renamer ==================== Main.sin' :: Double -> Double Main.sin' = $$(importDoubleToDouble "sin") Main.cos' :: Double -> Double Main.cos' = $$(importDoubleToDouble "cos") Main.main :: IO () Main.main = do print (Main.sin' 0) print (Main.cos' pi) ==================== Renamer ==================== ==================== Renamer ==================== foreign import ccall unsafe "cos" Main.cos :: Double -> Double }}} Not sure where to go with this now. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13587#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13587: addTopDecls fails with typed Template Haskell -------------------------------------+------------------------------------- Reporter: tmcdonell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.1-rc1 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 bgamari): My suspicion is that this is a result of the rather hacky way that we do dependency analysis for typed splices (where we just add everything in scope to the free variable set of the splice; see `Note [Free variables of typed splices]` in `RnSplice`) coupled with the fact that we don't run typed splices until type-checking (see `rnSpliceExpr`). This means that the declaration generated by the splice isn't present in the free variable set associated with the splice, causing us to fail during typechecking. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13587#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13587: addTopDecls fails with typed Template Haskell
-------------------------------------+-------------------------------------
Reporter: tmcdonell | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Template Haskell | Version: 8.2.1-rc1
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 Ben Gamari

#13587: addTopDecls fails with typed Template Haskell -------------------------------------+------------------------------------- Reporter: tmcdonell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.1-rc1 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 tmcdonell): Any new information on this one? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13587#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13587: addTopDecls fails with typed Template Haskell -------------------------------------+------------------------------------- Reporter: tmcdonell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.1-rc1 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 bgamari): * cc: simonpj, goldfire (added) Comment: I'm afraid not. I've CC'd Simon and Richard, both of whom know more about TH than me. That being said, if my suspicion from comment:5 is correct then this may be non-trivial to fix properly. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13587#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13587: addTopDecls fails with typed Template Haskell -------------------------------------+------------------------------------- Reporter: tmcdonell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #15437 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #15437 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13587#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13587: addTopDecls fails with typed Template Haskell -------------------------------------+------------------------------------- Reporter: tmcdonell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #15437 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): I have just run into this ticket. Is there anything that can be done to fix it? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13587#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13587: addTopDecls fails with typed Template Haskell -------------------------------------+------------------------------------- Reporter: tmcdonell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #15437 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): It's yet unclear to me why exactly this is failing. (Ben offered some speculation in comment:6, but it would be nice to confirm that this is indeed the case.) Once we have a proper diagnosis as to what the issue is, we can brainstorm possible solutions. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13587#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13587: addTopDecls fails with typed Template Haskell -------------------------------------+------------------------------------- Reporter: tmcdonell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.1-rc1 Resolution: | Keywords: | TypedTemplateHaskell Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #15437 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * keywords: => TypedTemplateHaskell -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13587#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC