[commit: ghc] master: Parser: commas_tup_tail duplicate SrcSpan on "Missing" value (72b21c3)
git at git.haskell.org
git at git.haskell.org
Thu Jun 18 14:19:31 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/72b21c393831b49867a296f19a2d039e48bb8dcd/ghc
>---------------------------------------------------------------
commit 72b21c393831b49867a296f19a2d039e48bb8dcd
Author: Alan Zimmerman <alan.zimm at gmail.com>
Date: Thu Jun 18 16:19:50 2015 +0200
Parser: commas_tup_tail duplicate SrcSpan on "Missing" value
Summary:
Parsing
{-# LANGUAGE TupleSections #-}
baz = (1, "hello", 6.5,,) 'a' (Just ())
Results in the following AST fragment
(L tests/examples/Tuple.hs:3:7-25
(ExplicitTuple
[ L tests/examples/Tuple.hs:3:8
(Present
(L tests/examples/Tuple.hs:3:8
(HsOverLit
(OverLit
(HsIntegral [ '1' ] 1)
PlaceHolder
(HsLit
(HsString
[]
{abstract:FastString}))
PlaceHolder))))
, L tests/examples/Tuple.hs:3:11-17
(Present
(L tests/examples/Tuple.hs:3:11-17
(HsLit
(HsString
[ '"'
, 'h'
, 'e'
, 'l'
, 'l'
, 'o'
, '"'
]
{abstract:FastString}))))
, L tests/examples/Tuple.hs:3:20-22
(Present
(L tests/examples/Tuple.hs:3:20-22
(HsOverLit
(OverLit
(HsFractional
(FL
[ '6' , '.' , '5' ]
(:% 13 2)))
PlaceHolder
(HsLit
(HsString
[]
{abstract:FastString}))
PlaceHolder))))
, L tests/examples/Tuple.hs:3:24
(Missing PlaceHolder)
, L tests/examples/Tuple.hs:3:24
(Missing PlaceHolder)
]
The final `Missing PlaceHolder` has a duplicated `SrcSpan`
Test Plan: ./validate
Reviewers: austin, hvr, bgamari
Reviewed By: bgamari
Subscribers: thomie, bgamari, mpickering
Differential Revision: https://phabricator.haskell.org/D995
GHC Trac Issues: #10537
>---------------------------------------------------------------
72b21c393831b49867a296f19a2d039e48bb8dcd
compiler/parser/Parser.y | 14 ++++----------
testsuite/tests/ghc-api/annotations/exampleTest.stdout | 3 +--
testsuite/tests/ghc-api/annotations/parseTree.stdout | 3 +--
3 files changed, 6 insertions(+), 14 deletions(-)
diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y
index 682b342..5414735 100644
--- a/compiler/parser/Parser.y
+++ b/compiler/parser/Parser.y
@@ -2386,28 +2386,22 @@ tup_exprs :: { [LHsTupArg RdrName] }
| commas tup_tail
{% do { mapM_ (\ll -> addAnnotation ll AnnComma ll) (fst $1)
; return
- (let tt = if null $2
- then [noLoc missingTupArg]
- else $2
- in map (\l -> L l missingTupArg) (fst $1) ++ tt) } }
+ (map (\l -> L l missingTupArg) (fst $1) ++ $2) } }
-- Always starts with commas; always follows an expr
commas_tup_tail :: { (SrcSpan,[LHsTupArg RdrName]) }
commas_tup_tail : commas tup_tail
{% do { mapM_ (\ll -> addAnnotation ll AnnComma ll) (tail $ fst $1)
; return (
- let tt = if null $2
- then [L (last $ fst $1) missingTupArg]
- else $2
- in (head $ fst $1
- ,(map (\l -> L l missingTupArg) (tail $ fst $1)) ++ tt)) } }
+ (head $ fst $1
+ ,(map (\l -> L l missingTupArg) (tail $ fst $1)) ++ $2)) } }
-- Always follows a comma
tup_tail :: { [LHsTupArg RdrName] }
: texp commas_tup_tail {% addAnnotation (gl $1) AnnComma (fst $2) >>
return ((L (gl $1) (Present $1)) : snd $2) }
| texp { [L (gl $1) (Present $1)] }
- | {- empty -} { [] {- [noLoc missingTupArg] -} }
+ | {- empty -} { [noLoc missingTupArg] }
-----------------------------------------------------------------------------
-- List expressions
diff --git a/testsuite/tests/ghc-api/annotations/exampleTest.stdout b/testsuite/tests/ghc-api/annotations/exampleTest.stdout
index cd6f9c0..210a4d8 100644
--- a/testsuite/tests/ghc-api/annotations/exampleTest.stdout
+++ b/testsuite/tests/ghc-api/annotations/exampleTest.stdout
@@ -1,10 +1,9 @@
---Problems---------------------
[
-(AK <no location info> AnnEofPos = [AnnotationTuple.hs:32:1])
]
---Problems'--------------------
-[(AnnEofPos, AnnotationTuple.hs:32:1)]
+[]
--------------------------------
[
(AK AnnotationTuple.hs:1:1 AnnCloseC = [AnnotationTuple.hs:27:1])
diff --git a/testsuite/tests/ghc-api/annotations/parseTree.stdout b/testsuite/tests/ghc-api/annotations/parseTree.stdout
index f7d1e5d..7d651aa 100644
--- a/testsuite/tests/ghc-api/annotations/parseTree.stdout
+++ b/testsuite/tests/ghc-api/annotations/parseTree.stdout
@@ -8,8 +8,7 @@
(AnnotationTuple.hs:16:20-22, [p], (6.5)),
(AnnotationTuple.hs:16:24, [m], ()),
(AnnotationTuple.hs:16:25, [m], ()),
- (AnnotationTuple.hs:16:26, [m], ()),
- (AnnotationTuple.hs:16:26, [m], ())]
+ (AnnotationTuple.hs:16:26, [m], ()), (<no location info>, [m], ())]
[
(AK AnnotationTuple.hs:1:1 AnnCloseC = [AnnotationTuple.hs:27:1])
More information about the ghc-commits
mailing list