[GHC] #13054: Generating unique names with template haskell

GHC ghc-devs at haskell.org
Wed Jun 14 17:01:52 UTC 2017


#13054: Generating unique names with template haskell
-------------------------------------+-------------------------------------
        Reporter:  tim-m89           |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Template Haskell  |              Version:  8.0.1
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by RyanGlScott):

 I recently ran into this with fixity declarations:

 {{{#!hs
 {-# LANGUAGE TemplateHaskell #-}
 module Bug where

 import Language.Haskell.TH

 $(do n1 <- newName "&&&"
      n2 <- newName "&&&"
      let mkDecs n = [ InfixD (Fixity 5 InfixL) n
                     , SigD n (AppT (AppT ArrowT (ConT ''Bool)) (AppT (AppT
 ArrowT (ConT ''Bool)) (ConT ''Bool)))
                     , FunD n [Clause [WildP,WildP] (NormalB (ConE 'False))
 []]
                     ]
      return (mkDecs n1 ++ mkDecs n2))
 }}}
 {{{
 $ /opt/ghc/8.2.1/bin/runghc -ddump-splices Bug.hs
 Bug.hs:(6,3)-(12,36): Splicing declarations
     do n1_a3Xj <- newName "&&&"
        n2_a3Xk <- newName "&&&"
        let mkDecs_a3Xl n_a3Xm
              = [InfixD (Fixity 5 InfixL) n_a3Xm,
                 SigD
                   n_a3Xm
                   (AppT
                      (AppT ArrowT (ConT ''Bool))
                      (AppT (AppT ArrowT (ConT ''Bool)) (ConT ''Bool))),
                 FunD n_a3Xm [Clause [WildP, WildP] (NormalB (ConE 'False))
 []]]
        return (mkDecs_a3Xl n1_a3Xj ++ mkDecs_a3Xl n2_a3Xk)
   ======>
     infixl 5 &&&_a4dl
     (&&&_a4dl) :: Bool -> Bool -> Bool
     (&&&_a4dl) _ _ = False
     infixl 5 &&&_a4dm
     (&&&_a4dm) :: Bool -> Bool -> Bool
     (&&&_a4dm) _ _ = False

 Bug.hs:6:3: error:
     Multiple fixity declarations for ‘&&&_a4dl’
     also at  Bug.hs:(6,3)-(12,36)
   |
 6 | $(do n1 <- newName "&&&"
   |   ^^^^^^^^^^^^^^^^^^^^^^...
 }}}

 (To be precise, you'd encounter the same issue if you commented out the
 line that gives you a fixity declaration, but that was the first place I
 noticed it.)

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13054#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list