#7092: Spurious shadowing warnings for names generated with newName
-----------------------------------------------+----------------------------
 Reporter:  a.ulrich                           |          Owner:                
  
     Type:  bug                                |         Status:  new           
  
 Priority:  normal                             |      Component:  Template 
Haskell
  Version:  7.4.2                              |       Keywords:                
  
       Os:  Linux                              |   Architecture:  x86           
  
  Failure:  Incorrect warning at compile-time  |       Testcase:                
  
Blockedby:                                     |       Blocking:                
  
  Related:                                     |  
-----------------------------------------------+----------------------------
 When multiple names are generated with newName in the same scope and with
 the same prefix argument for newName, ghc -Wall generates shadowing
 warnings although the names should be unique and no shadowing actually
 happens.

 {{{
 {-# LANGUAGE TemplateHaskell #-}
 module A where

 import Language.Haskell.TH

 code :: Q Exp
 code = do
   n1 <- newName "foo"
   n2 <- newName "foo"
   letE [valD (varP n1) (normalB [| (1 :: Int) |]) []]
        $ letE [valD (varP n2) (normalB [| (2 :: Int) |]) []]
        $ appE (appE [| ((+) :: Int -> Int -> Int)|] (varE n1)) (varE n2)
 }}}

 When loaded in ghci (7.4.2), warnings are generated:


 {{{
 [au@lift Trash]$ ghci -XTemplateHaskell -Wall -ddump-splices
 GHCi, version 7.4.2: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer-gmp ... linking ... done.
 Loading package base ... linking ... done.
 Prelude> :l a
 [1 of 1] Compiling A                ( a.hs, interpreted )
 Ok, modules loaded: A.
 *A> $(code)
 Loading package pretty-1.1.1.0 ... linking ... done.
 Loading package array-0.4.0.0 ... linking ... done.
 Loading package deepseq-1.3.0.0 ... linking ... done.
 Loading package containers-0.4.2.1 ... linking ... done.
 Loading package template-haskell ... linking ... done.
 <interactive>:3:3-6: Splicing expression
     code
   ======>
     let foo_aYh = 1 :: Int in
     let foo_aYi = 2 :: Int in (+) :: Int -> Int -> Int foo_aYh foo_aYi
 <interactive>:3:3-6: Splicing expression
     code
   ======>
     let foo_aYp = 1 :: Int in
     let foo_aYq = 2 :: Int in (+) :: Int -> Int -> Int foo_aYp foo_aYq
 <interactive>:3:3-6: Splicing expression
     code
   ======>
     let foo_aYx = 1 :: Int in
     let foo_aYy = 2 :: Int in (+) :: Int -> Int -> Int foo_aYx foo_aYy
 <interactive>:3:3-6: Splicing expression
     code
   ======>
     let foo_aYJ = 1 :: Int in
     let foo_aYK = 2 :: Int in (+) :: Int -> Int -> Int foo_aYJ foo_aYK

 <interactive>:3:3:
     Warning: This binding for `foo' shadows the existing binding
                bound at <interactive>:3:3

 <interactive>:3:3:
     Warning: This binding for `foo' shadows the existing binding
                bound at <interactive>:3:3
 3
 *A>
 }}}

 The spliced code looks like what I would expect: n1 and n2 are unique-
 looking names. The result is 3, so n1 does not actually seem to be
 shadowed by n2. Interestingly, the warnings only refer to the prefix "foo"
 and do not include the suffix appended by newName.


 {{{
 [au@lift Repositories]$ gcc -v
 Using built-in specs.
 COLLECT_GCC=gcc
 COLLECT_LTO_WRAPPER=/usr/lib/gcc/x86_64-linux-gnu/4.7/lto-wrapper
 Target: x86_64-linux-gnu
 Configured with: ../src/configure -v --with-pkgversion='Debian
 4.7.1-5' --with-bugurl=file:///usr/share/doc/gcc-4.7/README.Bugs
 --enable-languages=c,c++,go,fortran,objc,obj-c++ --prefix=/usr
 --program-suffix=-4.7 --enable-shared --enable-linker-build-id
 --with-system-zlib --libexecdir=/usr/lib --without-included-gettext
  --enable-threads=posix --with-gxx-include-dir=/usr/include/c++/4.7
 --libdir=/usr/lib --enable-nls --with-sysroot=/
 --enable-clocale=gnu --enable-libstdcxx-debug
 --enable-libstdcxx-time=yes --enable-gnu-unique-object
 --enable-plugin --enable-objc-gc --with-arch-32=i586
 --with-tune=generic --enable-checking=release
 --build=x86_64-linux-gnu --host=x86_64-linux-gnu
 --target=x86_64-linux-gnu
 Thread model: posix
 gcc version 4.7.1 (Debian 4.7.1-5)
 }}}

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