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

#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

#7918: SrcSpan's associated with expanded quasi-quotes are inconsistent ---------------------------------+------------------------------------------ Reporter: edsko | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.4.2 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | ---------------------------------+------------------------------------------ Changes (by simonpj): * status: new => infoneeded * difficulty: => Unknown Comment: Can you check with 7.6 or HEAD? Looks ok with HEAD to me: {{{ bash-3.1$ c:/code/HEAD/inplace/bin/ghc-stage2 -c T7918.hs -ddump-splices -fforce-recomp -ddump-rn -dppr-debug Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. Loading package array-0.4.0.2 ... linking ... done. Loading package deepseq-1.3.0.2 ... linking ... done. Loading package containers-0.5.0.0 ... linking ... done. Loading package pretty-1.1.1.0 ... linking ... done. Loading package template-haskell ... linking ... done. T7918.hs:4:7: T7918.hs:4:7-13: Splicing expression {T7918.hs:4:11-13} "a" ======> {T7918.hs:4:11-13} GHC.Types.True{d} T7918.hs:5:7: T7918.hs:5:7-13: Splicing expression {T7918.hs:5:11-13} "b" ======> {T7918.hs:5:11-13} GHC.Base.id{v} GHC.Types.True{d} T7918.hs:6:7: T7918.hs:6:7-13: Splicing expression {T7918.hs:6:11-13} "c" ======> {T7918.hs:6:11-13} (GHC.Types.True{d} GHC.Classes.||{v} GHC.Types.False{d}) T7918.hs:7:7: T7918.hs:7:7-13: Splicing expression {T7918.hs:7:11-13} "d" ======> {T7918.hs:7:11-13} GHC.Types.False{d} ==================== Renamer ==================== nonrec {T7918.hs:7:1-13} main:T7918.ex4{v r0} main:T7918.ex4{v r0} = {T7918.hs:7:7-13} ghc-prim:GHC.Types.False{(w) d 68} <> nonrec {T7918.hs:6:1-13} main:T7918.ex3{v r1} main:T7918.ex3{v r1} = {T7918.hs:6:7-13} (ghc-prim:GHC.Types.True{(w) d 6u} ghc-prim:GHC.Classes.||{v r1g} ghc-prim:GHC.Types.False{(w) d 68}) <> nonrec {T7918.hs:5:1-13} main:T7918.ex2{v r2} main:T7918.ex2{v r2} = {T7918.hs:5:7-13} base:GHC.Base.id{v r2q} ghc-prim:GHC.Types.True{(w) d 6u} <> nonrec {T7918.hs:4:1-13} main:T7918.ex1{v r3} main:T7918.ex1{v r3} = {T7918.hs:4:7-13} ghc-prim:GHC.Types.True{(w) d 6u} <> bash-3.1$ }}} Consistently 7-13. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7918#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (2)
-
GHC
-
GHC