Template Haskell of GHC 7.8 (again)

Kazu Yamamoto (=?iso-2022-jp?B?GyRCOzNLXE9CSScbKEI=?=) kazu at iij.ad.jp
Tue Mar 11 06:31:34 UTC 2014


Hi,

With the attached file, say Printf.hs, GHCi 7.6.3 works
as follows:

	% ghci Printf.hs 
	[1 of 1] Compiling Printf           ( Printf.hs, interpreted )
	Ok, modules loaded: Printf.
	> :set -XTemplateHaskell
	> putStrLn ( $(pr "Hello") )
	Hello

"Hello" is printed. Good. However, with GHC 7.8, the following error
occurs:

	% ghci Printf.hs 
	[1 of 1] Compiling Printf           ( Printf.hs, interpreted )
	Ok, modules loaded: Printf.
	> :set -XTemplateHaskell
	> putStrLn ( $(pr "Hello") )
	unknown package: main

Is this a bug of Template Haskell of GHC 7.8?

--Kazu
-------------- next part --------------
{-# LANGUAGE TemplateHaskell #-}
--
-- derived from: http://www.haskell.org/ghc/docs/latest/html/users_guide/template-haskell.html#th-example
--
module Printf (pr) where

import Language.Haskell.TH

data Format = D | S | L String

parse :: String -> [Format]
parse s   = [ L s ]

gen :: [Format] -> Q Exp
gen [D]   = [| \n -> show n |]
gen [S]   = [| \s -> s |]
gen [L s] = stringE s

-- |
--
-- >>> :set -XTemplateHaskell
-- >>> putStrLn ( $(pr "Hello") )
-- Hello
pr :: String -> Q Exp
pr s = gen (parse s)


More information about the ghc-devs mailing list