[GHC] #7918: SrcSpan's associated with expanded quasi-quotes are inconsistent

GHC cvs-ghc at haskell.org
Fri May 17 16:24:38 CEST 2013


#7918: SrcSpan's associated with expanded quasi-quotes are inconsistent
-----------------------------+----------------------------------------------
Reporter:  edsko             |          Owner:                  
    Type:  bug               |         Status:  new             
Priority:  normal            |      Component:  Compiler        
 Version:  7.4.2             |       Keywords:                  
      Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
 Failure:  None/Unknown      |      Blockedby:                  
Blocking:                    |        Related:                  
-----------------------------+----------------------------------------------
 Consider

 {{{
 {-# LANGUAGE TemplateHaskell #-}
 module A where
 import Language.Haskell.TH.Quote
 qq = QuasiQuoter {
          quoteExp  = \str -> case str of
                                 "a" -> [| True |]
                                 "b" -> [| id True |]
                                 "c" -> [| True || False |]
                                 "d" -> [| False |]
        , quotePat  = undefined
        , quoteType = undefined
        , quoteDec  = undefined
        }


 {-# LANGUAGE QuasiQuotes #-}
 module B where
 import A
 ex1 = [qq|a|]
 ex2 = [qq|b|]
 ex3 = [qq|c|]
 ex4 = [qq|d|]
 }}}

 In the expansion of `[qq|a|]` the source span for `True` is reported as
 4:7-4:14 and 7:7-7:14 respectively -- i.e., the span of the entire quasi-
 quote. However, for the expansion of `[qq|b|]` and `[qq|c|]` the source
 span for `id`, `True`, `False`, and `(||)` are all reported as 5:11-5:14 /
 6:11-6:14, i.e., starting at the "contents" of the quasi-quote.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7918>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler



More information about the ghc-tickets mailing list