#4491: dataToQa uses only unqualified names when converting values to their TH
representation.
---------------------------------+------------------------------------------
    Reporter:  gmainland         |       Owner:                  
        Type:  bug               |      Status:  new             
    Priority:  normal            |   Component:  Template Haskell
     Version:  6.12.3            |    Keywords:                  
    Testcase:                    |   Blockedby:                  
          Os:  Unknown/Multiple  |    Blocking:                  
Architecture:  Unknown/Multiple  |     Failure:  None/Unknown    
---------------------------------+------------------------------------------
 The `dataToQa` function in Language.Haskell.TH.Quote always use
 unqualified names when converting a value to its TH representation, even
 if the names are not in scope in the TH splice where they are called.

 I have attached a patch that makes things a bit better, but there are
 still a number of outstanding issues.

 The problem is that the `Data` type class allows one to find the name of
 the module in which a data constructor is declared, but it does not allow
 one to find the name of the '''package''' in which the constructor is
 declared. On the other hand, TH lets you either create a qualified name
 that is resolved using the namespace in effect at the point of a TH
 splice, or create a fully resolved name '''if''' you know the package in
 which it is declared. The patch I have attached changes `dataToQa` to
 create all names as qualified names, but the resulting TH only compiles
 without error if the data constructors that are used are imported in such
 a way that they can be qualified with the name of the module in which they
 are declared. Examples that assume the new definition of dataToQa follow.

 Assume the file A.hs exists with the contents:

 {{{
 {-# LANGUAGE DeriveDataTypeable #-}

 module A where

 import Data.Generics

 data Foo = Foo Int
   deriving (Show, Data, Typeable)
 }}}

 Now this program will run and print `Foo 1`:

 {{{
 {-# LANGUAGE TemplateHaskell #-}

 import Language.Haskell.TH

 import A

 main :: IO ()
 main = print $(dataToExpQ (const Nothing) (Foo 1))
 }}}

 So will this program:

 {{{
 {-# LANGUAGE TemplateHaskell #-}

 import Language.Haskell.TH

 import qualified A

 main :: IO ()
 main = print $(dataToExpQ (const Nothing) (A.Foo 1))
 }}}

 But this program will not compile:

 {{{
 {-# LANGUAGE TemplateHaskell #-}

 import Language.Haskell.TH

 import A as B

 main :: IO ()
 main = print $(dataToExpQ (const Nothing) (Foo 1))
 }}}

 Instead it gives the following error:

 {{{
 Not in scope: data constructor `A.Foo'
 In the first argument of `print', namely
     `$(dataToExpQ (const Nothing) (Foo 1))'
 In the expression: print ($(dataToExpQ (const Nothing) (Foo 1)))
 In the definition of `main':
     main = print ($(dataToExpQ (const Nothing) (Foo 1)))
 }}}

 This is expected, since `dataToQa` creates TH qualified names but uses the
 resolved module name, `A`, as the qualifier.

 The current (unpatched) version of `dataToQa` creates all TH names using
 `mkName`, i.e., it creates all names unqualified. I think always using
 qualified names instead is preferable. It may break existing code, but it
 gives the programmer better control (that is, some control!) over
 namespace pollution.

 There are two better solutions.

 The first would be to change the `Data` type class so that it exposes the
 package name as well as the module name in which data constructors are
 declared. This seems GHC-specific though and a bit of a hack.

 I think the ideal solution is to add a smart TH name constructor that
 allows one to create a '''resolved''' name by specifying the resolved
 module name '''without''' requiring that the package name be specified. Of
 course if different packages define the same data constructor and they
 both happen to be in scope where the splice occurs, then there will be a
 static error, but I suspect this would only happen in a module that uses
 `PackageImports`, and even then it would be rare. This might require
 adding a member to the `Q` monad that allows "resolving" names or
 something, which I'm sure is non-trivial. I would be willing to work on a
 patch if given a few hints on how to approach the problem and assuming
 there's a willingness to adopt such a patch.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4491>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to