[GHC] #12452: TemplateHaskell - variables in top level splices and loading modules.
GHC
ghc-devs at haskell.org
Tue Aug 2 11:45:25 UTC 2016
#12452: TemplateHaskell - variables in top level splices and loading modules.
-------------------------------------+-------------------------------------
Reporter: mkloczko | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Keywords: | Operating System: Linux
TemplateHaskell |
Architecture: x86_64 | Type of failure: GHC rejects
(amd64) | valid program
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
The following code fails when loading Main module:
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ScopedTypeVariables #-}
module TH where
import Language.Haskell.TH
import Language.Haskell.TH.Syntax
import Data.Typeable
usingType :: a -> Q [Dec]
usingType _ = do
let name = "The name!"
-- theF = "The name!"
return [FunD (mkName "theF") [Clause [] (NormalB $ LitE $ StringL name
) []]]
}}}
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
module Main where
import TH
data A = A Int
-- Runs with `usingType (undefined :: A)` instead
$(usingType (A 3) )
main = putStrLn $ theF
}}}
The error:
{{{
$ ghc --make Main.hs
[1 of 2] Compiling TH ( TH.hs, TH.o )
[2 of 2] Compiling Main ( Main.hs, Main.o )
attempting to use module ‘Main’ (Main.hs) which is not loaded
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12452>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list