[GHC] #15865: Typed template haskell and implicit parameters lead to incorrect results

#15865: Typed template haskell and implicit parameters lead to incorrect results -------------------------------------+------------------------------------- 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: -------------------------------------+------------------------------------- In a similar vein to #15863 but this time with implicit parameters. https://gist.github.com/b6919b13abe0954fdad844e16e0edb48 {{{ {-# LANGUAGE ImplicitParams #-} {-# LANGUAGE TemplateHaskell #-} module A where import Language.Haskell.TH import Data.List (sortBy) sort :: (?cmp :: a -> a -> Ordering) => [a] -> [a] sort = sortBy ?cmp me :: Q (TExp ([Int] -> [Int])) me = let ?cmp = compare in [|| sort ||] }}} In module `A` we quote a value which has an implicit argument but in its context we bind the implicit so the type of the quote is the monomorphic type. {{{ {-# LANGUAGE ImplicitParams #-} {-# LANGUAGE TemplateHaskell #-} module B where import A foo :: [Int] -> [Int] foo = --let ?cmp = compare in $$(me) }}} When we splice in `me`, we get an error about an unbound implicit parameter which is totally bogus as we already bound it in `A`. There is also dynamic binding if another implicit parameter with the same name is in scope but the type of `me` mentions nothing about implicit parameters so this shouldn't be allowed. {{{ B.hs:8:10: error: • Unbound implicit parameter (?cmp::Int -> Int -> Ordering) arising from a use of ‘sort’ • In the expression: sort In the result of the splice: $me To see what the splice expanded to, use -ddump-splices In the Template Haskell splice $$(me) | 8 | foo = $$(me) | ^^ Failed, one module loaded. }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15865 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15865: Typed template haskell and implicit parameters lead to incorrect results -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.1 Resolution: | Keywords: | TypedTemplateHaskell 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 mpickering): * keywords: => TypedTemplateHaskell -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15865#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15865: Typed template haskell and implicit parameters lead to incorrect results -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.6.1 Resolution: | Keywords: | TypedTemplateHaskell 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 goldfire): * component: Compiler => Template Haskell -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15865#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15865: Typed template haskell and implicit parameters lead to incorrect results
-------------------------------------+-------------------------------------
Reporter: mpickering | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Template Haskell | Version: 8.6.1
Resolution: | Keywords:
| TypedTemplateHaskell
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 Marge Bot
participants (1)
-
GHC