#877: Template Haskell doesn't parse data decls properly
------------------------------------+---------------------------------------
    Reporter:  [EMAIL PROTECTED]  |        Owner:                               
 
        Type:  bug                  |       Status:  new                        
   
    Priority:  normal               |    Milestone:                             
   
   Component:  Compiler             |      Version:  6.4.2                      
   
    Severity:  normal               |     Keywords:  Template TH parsing 
identifier
          Os:  Windows              |   Difficulty:  Unknown                    
   
Architecture:  x86                  |  
------------------------------------+---------------------------------------
Hi,
 Template Haskell is rejecting data decls just because of the particular
 identifier I'm choosing to use. The code is:
 {{{
    module Box where

    data T = T Int
 }}}
 {{{
 {-# OPTIONS_GHC -fglasgow-exts -fth #-}
 module Main where

 import qualified Box as Box

 $( [d| data T = T Box.T |] )

 main = return ()
 }}}
 And the error message is:
 {{{
 main.hs:6:18: Not in scope: type constructor or class `Box.T'
 }}}
 If I change the decl in the splice to:
 {{{
     $( [d| data Hello = T Box.T |] )
 }}}
 the code compiles with no problems! (???)
 I thought I could workaround the issue by adding
 {{{
     type T = Hello
 }}}
 but although this workaround works in the simple example above, in my
 actual program I get a {{{ghc panic}}} error that I don't know how to
 reproduce in a simple example.

 The problem seems to be that I'm using the name {{{T}}} for both types,
 but I'd prefer to do this as it's consistent with the rest of my code
 (this coding style is recommended by Henning at the bottom of the page
 [http://haskell.org/hawiki/UsingQualifiedNames])

 The only workaround seems to be to declare a type synonym for Box.T ie:
 {{{
   type BoxT = Box.T

   $( [d| data T = T BoxT |] )
 }}}
 but while this is ok it's not ideal as then type synonyms have to be
 defined in each module instead of just being able to use the neat
 qualified naming syntax. Also it is strange because the normal decl
 {{{
      data T = T Box.T
 }}}
 works fine, so decls in [d| |] brackets must be being parsed differently
 from normal top level decls for some reason (I'm new to TH so I don't know
 why).

 (The reason I'm doing this is to get extra fields added automatically to a
 record (and methods to an instance decl) to implement one level of inlined
 OO implementation inheritance in Haskell)

 Anyway it's not essential, just a bit strange. I'll use the BoxT synonym
 for the moment.

 Regards, Brian.

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

Reply via email to