[GHC] #10596: Template Haskell : getQ and putQ doesn't work
GHC
ghc-devs at haskell.org
Thu Jul 2 04:36:04 UTC 2015
#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
More information about the ghc-tickets
mailing list