[GHC] #8499: Template Haskell: newName not new enough
GHC
ghc-devs at haskell.org
Mon Nov 4 01:26:07 UTC 2013
#8499: Template Haskell: newName not new enough
------------------------------------+-------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Template Haskell | Version: 7.7
Keywords: | Operating System: Unknown/Multiple
Architecture: Unknown/Multiple | Type of failure: None/Unknown
Difficulty: Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: |
------------------------------------+-------------------------------------
When I compile this:
{{{
{-# LANGUAGE TemplateHaskell, PolyKinds, DataKinds #-}
{-# OPTIONS_GHC -Wall #-}
import Language.Haskell.TH
$( do TyConI (DataD _ _ [PlainTV tvb_a] _ _) <- reify ''Maybe
my_a <- newName "a"
return [TySynD (mkName "SMaybe") [KindedTV my_a (AppT (ConT ''Maybe)
(VarT tvb_a))]
(TupleT 0)] )
}}}
I get this:
{{{
/Users/rae/temp/Bug.hs:6:4: Warning:
This binding for ‛a’ shadows the existing binding
bound at /Users/rae/temp/Bug.hs:6:4
}}}
The problem is that, in the library definition for `Maybe`, the name of
its type variable is `a`. In my Template Haskell code, I read in `Maybe`'s
definition (using `reify`) to extract the name of `Maybe`'s type variable.
I then create a new name, also seeded with `"a"`. Then, I create a type
synonym definition
{{{
type SMaybe (a_newName :: Maybe a_Maybe) = ()
}}}
where `a_newName` is the variable I `newName`d, and `a_Maybe` is the name
I slurped from `Maybe`'s definition. These variables print with different
uniques, but the warning comes up anyway.
This problem actually came up in real code (singletons library), where I'm
trying to get the generated code to be warning-free.
This was tested on 7.7.20131031.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8499>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list