[GHC] #10596: Template Haskell : getQ and putQ doesn't work

#10596: Template Haskell : getQ and putQ doesn't work -------------------------------------+------------------------------------- Reporter: kiripon | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 7.10.1 Haskell | Operating System: Unknown/Multiple Keywords: getQ putQ | Type of failure: None/Unknown Architecture: | Blocked By: Unknown/Multiple | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Functions `getQ` and `putQ` in the module `Language.Haskell.TH.Syntax` do not work. Following code is an example of this problem. The variable `x` should be `(Just B)`, but `x` is `Nothing`. {{{#!hs {-# LANGUAGE TemplateHaskell #-} module X where import Language.Haskell.TH import Language.Haskell.TH.Syntax do putQ (100 :: Int) x <- getQ :: Q (Maybe Int) -- It should print "Just 100" but "Nothing" runIO $ print x return [] }}} As a result, I get following output on compile. {{{#!hs $ ghc -fforce-recomp X.hs [1 of 1] Compiling X ( X.hs, X.o ) Nothing }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10596 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10596: Template Haskell : getQ and putQ doesn't work -------------------------------------+------------------------------------- Reporter: kiripon | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: getQ putQ Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by ezyang): Bug is quite simple (wrong type is used for lookup), fix on the way... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10596#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10596: Template Haskell : getQ and putQ doesn't work -------------------------------------+------------------------------------- Reporter: kiripon | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: getQ putQ Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by kiripon): I fixed this bug and checked work correctly. {{{ diff --git a/compiler/typecheck/TcSplice.hs b/compiler/typecheck/TcSplice.hs index a7363d8..2bcb78c 100644 --- a/compiler/typecheck/TcSplice.hs +++ b/compiler/typecheck/TcSplice.hs @@ -836,7 +836,7 @@ instance TH.Quasi (IOEnv (Env TcGblEnv TcLclEnv)) where qGetQ = do th_state_var <- fmap tcg_th_state getGblEnv th_state <- readTcRef th_state_var - let x = Map.lookup (typeOf x) th_state >>= fromDynamic + let x = Map.lookup (typeOf $ fromJust x) th_state >>= fromDynamic return x qPutQ x = do diff --git a/compiler/typecheck/TcSplice.hs b/compiler/typecheck/TcSplice.hs }}} {{{ kiripon% ghc -fforce-recomp Y.hs [1 of 1] Compiling Y ( Y.hs, Y.o ) Nothing Nothing kiripon% $HOME/opt/local/ghc-head/bin/ghc -fforce-recomp Y.hs [1 of 1] Compiling Y ( Y.hs, Y.o ) Just 100 Just 100 kiripon% cat Y.hs {-# LANGUAGE TemplateHaskell #-} module Y where import Language.Haskell.TH import Language.Haskell.TH.Syntax -- splice for testing getQ and putQ do putQ (100 :: Int) :: Q () x <- getQ :: Q (Maybe Int) runIO $ print x -- prints Nothing return [] do x <- getQ :: Q (Maybe Int) runIO $ print x -- prints Nothing return [] kiripon% }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10596#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10596: Template Haskell : getQ and putQ doesn't work -------------------------------------+------------------------------------- Reporter: kiripon | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: getQ putQ Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1026 -------------------------------------+------------------------------------- Changes (by ezyang): * differential: => Phab:D1026 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10596#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10596: Template Haskell : getQ and putQ doesn't work
-------------------------------------+-------------------------------------
Reporter: kiripon | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Template Haskell | Version: 7.10.1
Resolution: | Keywords: getQ putQ
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Blocked By: | Test Case:
Related Tickets: | Blocking:
| Differential Revisions: Phab:D1026
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#10596: Template Haskell : getQ and putQ doesn't work -------------------------------------+------------------------------------- Reporter: kiripon | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: getQ putQ Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1026 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10596#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10596: Template Haskell : getQ and putQ doesn't work -------------------------------------+------------------------------------- Reporter: kiripon | Owner: Type: bug | Status: merge Priority: normal | Milestone: 7.10.3 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: getQ putQ Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1026 -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 7.10.3 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10596#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10596: Template Haskell : getQ and putQ doesn't work -------------------------------------+------------------------------------- Reporter: kiripon | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: getQ putQ Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: th/T10596 Related Tickets: | Blocking: | Differential Revisions: Phab:D1026 -------------------------------------+------------------------------------- Changes (by thomie): * status: merge => new * testcase: => th/T10596 Comment: This test is failing on Windows, and also on Travis (https://s3.amazonaws.com/archive.travis-ci.org/jobs/70789702/log.txt). {{{ Actual stderr output differs from expected: --- ./th/T10596.stderr.normalised 2015-07-13 19:47:37.667428464 +0000 +++ ./th/T10596.comp.stderr.normalised 2015-07-13 19:47:37.667428464 +0000 @@ -1 +0,0 @@ -Just 100 \ No newline at end of file *** unexpected failure for T10596(normal) }}} Note that Windows and Travis don't build dynamic libraries. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10596#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10596: Template Haskell : getQ and putQ doesn't work
-------------------------------------+-------------------------------------
Reporter: kiripon | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 7.10.3
Component: Template Haskell | Version: 7.10.1
Resolution: | Keywords: getQ putQ
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Blocked By: | Test Case: th/T10596
Related Tickets: | Blocking:
| Differential Revisions: Phab:D1026
-------------------------------------+-------------------------------------
Comment (by Joachim Breitner

#10596: Template Haskell : getQ and putQ doesn't work -------------------------------------+------------------------------------- Reporter: kiripon | Owner: Type: bug | Status: merge Priority: normal | Milestone: 7.10.3 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: getQ putQ Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: th/T10596 Related Tickets: | Blocking: | Differential Revisions: Phab:D1026 -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => merge Comment: According to [https://travis-ci.org/ghc/ghc/builds/71040095 Travis], this fix works. Thanks for thinking of this, Joachim! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10596#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10596: Template Haskell : getQ and putQ doesn't work -------------------------------------+------------------------------------- Reporter: kiripon | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.10.3 Component: Template Haskell | Version: 7.10.1 Resolution: fixed | Keywords: getQ putQ Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: th/T10596 Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1026 -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-7.10`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10596#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC