
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 {-# LANGUAGE TemplateHaskell #-} -- -- derived from: http://www.haskell.org/ghc/docs/latest/html/users_guide/template-haskell.htm... -- 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)

Yes: https://ghc.haskell.org/trac/ghc/ticket/8833 Austin is looking at this for the 7.8 release Simon | -----Original Message----- | From: ghc-devs [mailto:ghc-devs-bounces@haskell.org] On Behalf Of Kazu | Yamamoto | Sent: 11 March 2014 06:32 | To: ghc-devs@haskell.org | Subject: Template Haskell of GHC 7.8 (again) | | 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

Hi,
Yes: https://ghc.haskell.org/trac/ghc/ticket/8833 Austin is looking at this for the 7.8 release
Thanks. I guess you meant: https://ghc.haskell.org/trac/ghc/ticket/8831 --Kazu

Bother. Yes, correct. | -----Original Message----- | From: Kazu Yamamoto [mailto:kazu@iij.ad.jp] | Sent: 11 March 2014 11:58 | To: Simon Peyton Jones | Cc: ghc-devs@haskell.org | Subject: Re: Template Haskell of GHC 7.8 (again) | | Hi, | | > Yes: https://ghc.haskell.org/trac/ghc/ticket/8833 | > Austin is looking at this for the 7.8 release | | Thanks. I guess you meant: | https://ghc.haskell.org/trac/ghc/ticket/8831 | | --Kazu
participants (2)
-
Kazu Yamamoto
-
Simon Peyton Jones