[GHC] #9813: Error when reifying type constructor
GHC
ghc-devs at haskell.org
Wed Nov 19 21:42:07 UTC 2014
#9813: Error when reifying type constructor
-------------------------------------+-------------------------------------
Reporter: owst | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.3
Keywords: | Operating System:
Architecture: Unknown/Multiple | Unknown/Multiple
Difficulty: Unknown | Type of failure:
Blocked By: | None/Unknown
Related Tickets: | Test Case:
| Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
The following code works under ghc-7.6.3 and template-haskell-2.8.0.0:
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
data Huh = ThisDefinitely
| UsedToWork
constructorNames :: String
constructorNames = $(do
ty <- reify ''Huh
let showCon (NormalC n _) = nameBase n
strs = case ty of
(TyConI (DataD _ _ _ cons _)) -> map showCon cons
return . LitE . StringL $ concat strs)
main = putStrLn constructorNames
}}}
Printing the following at compile time:
{{{
[1 of 1] Compiling Main ( Main.hs, Main.o )
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package array-0.4.0.1 ... linking ... done.
Loading package deepseq-1.3.0.1 ... linking ... done.
Loading package containers-0.5.0.0 ... linking ... done.
Loading package pretty-1.1.1.0 ... linking ... done.
Loading package template-haskell ... linking ... done.
Linking Main ...
}}}
and then successfully executing:
{{{
$ ./Main
ThisDefinitelyUsedToWork
}}}
However, using ghc 7.8.3/template-haskell-2.9.0.0 I get the following
compile error:
{{{
[1 of 1] Compiling Main ( Main.hs, Main.o )
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package array-0.5.0.0 ... linking ... done.
Loading package deepseq-1.3.0.2 ... linking ... done.
Loading package containers-0.5.5.1 ... linking ... done.
Loading package pretty-1.1.1.1 ... linking ... done.
Loading package template-haskell ... linking ... done.
Main.hs:8:22:
‘Huh’ is not in the type environment at a reify
In the splice:
$(do { ty <- reify ''Huh;
let showCon (NormalC n _) = ...
....;
return . LitE . StringL $ concat strs })
}}}
Is this expected? I couldn't see anything in the GHC release notes to
suggest this should no longer work.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9813>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list