
#15835: Internal error when splicing value constructed using typed template haskell -------------------------------------+------------------------------------- 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: -------------------------------------+------------------------------------- Related to #15833 Compiling Test.hs leads to an internal compiler error. https://gist.github.com/f04a613bb5e20c241c5b91c2f38b8f06 {{{ {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -ddump-splices #-} module Test where import qualified Compiler as C main :: IO () main = do $$(C.runQuery) }}} {{{ {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} {-# OPTIONS_GHC -Wall #-} module Compiler where import Language.Haskell.TH type QTExp a = Q (TExp a) fix :: (a -> a) -> a fix f = let x = f x in x while :: forall m . Monoid m => QTExp (IO m -> IO m) -> QTExp (IO m) while b = [|| fix (\r -> whenM @(IO m) ($$b r)) ||] whenM :: Monoid m => m -> m whenM _ = mempty execOp :: forall m . Monoid m => QTExp (IO m) execOp = while [|| \r -> $$(while @m [|| id ||]) >> r ||] runQuery :: QTExp (IO ()) runQuery = execOp }}} Leads to the following internal errors even though `Compiler` type checked. {{{ Prelude> :r [1 of 2] Compiling Compiler ( Compiler.hs, interpreted ) [2 of 2] Compiling Test ( Test.hs, interpreted ) Test.hs:9:6-15: Splicing expression C.runQuery ======> C.fix (\ r_a7K7 -> (C.whenM @(IO m_a7Gp)) ((\ r_a7K8 -> ((C.fix (\ r_a7K9 -> (C.whenM @(IO m_a7Gp)) (id r_a7K9))) >> r_a7K8)) r_a7K7)) Test.hs:9:6: error: • The exact Name ‘m’ 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 result of the splice: $C.runQuery To see what the splice expanded to, use -ddump-splices In the Template Haskell splice $$(C.runQuery) In a stmt of a 'do' block: $$(C.runQuery) | 9 | $$(C.runQuery) | ^^^^^^^^^^ Test.hs:9:6: error: • The exact Name ‘m’ 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 result of the splice: $C.runQuery To see what the splice expanded to, use -ddump-splices In the Template Haskell splice $$(C.runQuery) In a stmt of a 'do' block: $$(C.runQuery) | 9 | $$(C.runQuery) | ^^^^^^^^^^ Test.hs:9:6: error: • GHC internal error: ‘m’ is not in scope during type checking, but it passed the renamer tcl_env of environment: [a7K7 :-> Identifier[r_a7K7::a0, NotLetBound], r5Fg :-> Identifier[main::IO (), TopLevelLet [] True]] • In the first argument of ‘IO’, namely ‘m’ In the type ‘(IO m)’ In the expression: (C.whenM @(IO m)) ((\ r_a7K8 -> ((C.fix (\ r_a7K9 -> (C.whenM @(IO m)) (id r_a7K9))) >> r_a7K8)) r_a7K7) | 9 | $$(C.runQuery) | }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15835 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler