
#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