#5665: Duplicate asm symbols for record fields when TH is used in the module
-----------------------------------+----------------------------------------
    Reporter:  mikhail.vorozhtsov  |       Owner:              
        Type:  bug                 |      Status:  new         
    Priority:  normal              |   Component:  Compiler    
     Version:  7.3                 |    Keywords:              
    Testcase:                      |   Blockedby:              
          Os:  Unknown/Multiple    |    Blocking:              
Architecture:  Unknown/Multiple    |     Failure:  None/Unknown
-----------------------------------+----------------------------------------
 {{{
 $ cat TH.hs
 module TH where

 import Language.Haskell.TH

 doSomeTH s tp = return [NewtypeD [] n [] (NormalC n [(NotStrict, ConT
 tp)]) []]
   where n = mkName s
 $ cat Bug.hs
 {-# LANGUAGE TemplateHaskell #-}

 module Bug where

 import TH

 data Record = Record { recordField :: Int }

 $(doSomeTH "SomeType" ''Int)
 $ ghc-7.3.20111128 -fforce-recomp TH.hs Bug.hs
 [1 of 2] Compiling TH               ( TH.hs, TH.o )
 [2 of 2] Compiling Bug              ( Bug.hs, Bug.o )
 Loading package ghc-prim ... linking ... done.
 Loading package integer-gmp ... linking ... done.
 Loading package base ... linking ... done.
 Loading package pretty-1.1.0.0 ... linking ... done.
 Loading package array-0.3.0.3 ... linking ... done.
 Loading package deepseq-1.2.0.1 ... linking ... done.
 Loading package containers-0.4.2.0 ... linking ... done.
 Loading package template-haskell ... linking ... done.
 /tmp/ghc29791_0/ghc29791_0.s: Assembler messages:

 /tmp/ghc29791_0/ghc29791_0.s:54:0:
      Error: symbol `Bug_recordField_closure' is already defined

 /tmp/ghc29791_0/ghc29791_0.s:74:0:
      Error: symbol `Bug_recordField_info' is already defined
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5665>
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