[GHC] #15437: Internal error when applying a scoped type variable inside a typed expression quotation

#15437: Internal error when applying a scoped type variable inside a typed expression quotation -------------------------------------+------------------------------------- Reporter: dminuoso | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 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: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE TemplateHaskell #-} import TestMod f :: Int f = $$(foo) main :: IO () main = main }}} {{{#!hs {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeApplications #-} module TestMod where import Language.Haskell.TH.Syntax (Q, TExp) get :: forall a. Int get = 1 foo :: forall a. Q (TExp Int) foo = [|| get @a ||] }}} {{{ Test.hs:6:8: error: • The exact Name ‘a’ 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: $foo To see what the splice expanded to, use -ddump-splices In the Template Haskell splice $$(foo) In the expression: $$(foo) | 6 | f = $$(foo) | ^^^ Test.hs:6:8: error: • GHC internal error: ‘a’ is not in scope during type checking, but it passed the renamer tcl_env of environment: [r3Kl :-> Identifier[f::Int, TopLevelLet [] True], r3PI :-> Identifier[main::IO (), TopLevelLet [r3PI :-> main] True]] • In the type ‘a’ In the expression: get @a In the result of the splice: $foo To see what the splice expanded to, use -ddump-splices | 6 | f = $$(foo) | }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15437 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15437: Internal error when applying a scoped type variable inside a typed expression quotation -------------------------------------+------------------------------------- Reporter: dminuoso | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Template Haskell | Version: 8.4.3 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 simonpj): * component: Compiler => Template Haskell -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15437#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15437: Internal error when applying a scoped type variable inside a typed expression quotation -------------------------------------+------------------------------------- Reporter: dminuoso | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Template Haskell | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13587 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #13587 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15437#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15437: Internal error when applying a scoped type variable inside a typed expression quotation -------------------------------------+------------------------------------- Reporter: dminuoso | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Template Haskell | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13587, #15835 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * related: #13587 => #13587, #15835 Comment: Also #15835 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15437#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15437: Internal error when applying a scoped type variable inside a typed expression quotation -------------------------------------+------------------------------------- Reporter: dminuoso | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Template Haskell | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13587, #15835 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): I don't think types are really dealt with properly in typed template haskell. Your program is a lot like {{{ foo :: Int -> Q (TExp Int) foo x = [|| x ||] }}} In this case, we have to interpret the `x` as `$(lift x)` and we should do the same thing for types here. To go back to your program and some pseudo syntax: {{{ foo :: forall a. Q (TExp Int) foo = [|| get @$(lift a) ||] }}} We really mean something like this as the value of `a` is bound at compile-time but not at run-time so if we want to use it we have to use it in a splice. Does that sound sensible Simon? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15437#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15437: Internal error when applying a scoped type variable inside a typed expression quotation -------------------------------------+------------------------------------- Reporter: dminuoso | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Template Haskell | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13587, #15835 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): I put a patch up which contains the test for now. https://phabricator.haskell.org/D5291 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15437#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15437: Internal error when applying a scoped type variable inside a typed
expression quotation
-------------------------------------+-------------------------------------
Reporter: dminuoso | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.8.1
Component: Template Haskell | Version: 8.4.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #13587, #15835 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#15437: Internal error when applying a scoped type variable inside a typed expression quotation -------------------------------------+------------------------------------- Reporter: dminuoso | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Template Haskell | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: T15437 Blocked By: | Blocking: Related Tickets: #13587, #15835 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * testcase: => T15437 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15437#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15437: Internal error when applying a scoped type variable inside a typed expression quotation -------------------------------------+------------------------------------- Reporter: dminuoso | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.10.1 Component: Template Haskell | Version: 8.4.3 Resolution: | Keywords: | TypedTemplateHaskell Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: T15437 Blocked By: | Blocking: Related Tickets: #13587, #15835 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * keywords: => TypedTemplateHaskell -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15437#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15437: Internal error when applying a scoped type variable inside a typed expression quotation -------------------------------------+------------------------------------- Reporter: dminuoso | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.10.1 Component: Template Haskell | Version: 8.4.3 Resolution: | Keywords: | TypedTemplateHaskell Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: T15437 Blocked By: | Blocking: Related Tickets: #13587, #15835 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): I have a patch which fixes the issue presented in this ticket but there are some rough edges and design considerations which need to be dealt with. https://gitlab.haskell.org/ghc/ghc/merge_requests/166 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15437#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15437: Internal error when applying a scoped type variable inside a typed expression quotation -------------------------------------+------------------------------------- Reporter: dminuoso | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.10.1 Component: Template Haskell | Version: 8.4.3 Resolution: | Keywords: | TypedTemplateHaskell Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: T15437 Blocked By: | Blocking: Related Tickets: #13587, #15835 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): Patch is now ready for preliminary review: https://gitlab.haskell.org/ghc/ghc/merge_requests/166 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15437#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC