[commit: ghc] wip/7.10-api-annots: ApiAnnotations : AnnComma missing in TupleSection (2f463c7)
git at git.haskell.org
git at git.haskell.org
Fri May 8 17:02:28 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/7.10-api-annots
Link : http://ghc.haskell.org/trac/ghc/changeset/2f463c75ca0ef019d65e7528f8546e46a29bb5b6/ghc
>---------------------------------------------------------------
commit 2f463c75ca0ef019d65e7528f8546e46a29bb5b6
Author: Alan Zimmerman <alan.zimm at gmail.com>
Date: Fri May 8 09:38:39 2015 +0200
ApiAnnotations : AnnComma missing in TupleSection
Summary:
For the following code
{-# LANGUAGE TupleSections #-}
foo = do
liftIO $ atomicModifyIORef ciTokens ((,()) . f)
the annotation is missing for the comma.
Test Plan: ./validate
Reviewers: hvr, austin
Reviewed By: austin
Subscribers: bgamari, thomie
Differential Revision: https://phabricator.haskell.org/D834
GHC Trac Issues: #10280
(cherry picked from commit 225df19a87d8de8245db84d558618f4824631acc)
>---------------------------------------------------------------
2f463c75ca0ef019d65e7528f8546e46a29bb5b6
compiler/parser/Parser.y | 4 +--
testsuite/tests/ghc-api/annotations/.gitignore | 1 +
testsuite/tests/ghc-api/annotations/Makefile | 5 +++
testsuite/tests/ghc-api/annotations/T10280.stderr | 6 ++++
testsuite/tests/ghc-api/annotations/T10280.stdout | 36 ++++++++++++++++++++++
testsuite/tests/ghc-api/annotations/Test10280.hs | 4 +++
testsuite/tests/ghc-api/annotations/all.T | 1 +
.../ghc-api/annotations/{t10269.hs => t10280.hs} | 2 +-
8 files changed, 56 insertions(+), 3 deletions(-)
diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y
index b2f702d..9645e3a 100644
--- a/compiler/parser/Parser.y
+++ b/compiler/parser/Parser.y
@@ -2252,10 +2252,10 @@ texp :: { LHsExpr RdrName }
tup_exprs :: { [LHsTupArg RdrName] }
: texp commas_tup_tail
{% do { addAnnotation (gl $1) AnnComma (fst $2)
- ; return ((L (gl $1) (Present $1)) : snd $2) } }
+ ; return ((sL1 $1 (Present $1)) : snd $2) } }
| commas tup_tail
- {% do { mapM_ (\ll -> addAnnotation (gl ll) AnnComma (gl ll)) $2
+ {% do { mapM_ (\ll -> addAnnotation ll AnnComma ll) (fst $1)
; return
(let tt = if null $2
then [noLoc missingTupArg]
diff --git a/testsuite/tests/ghc-api/annotations/.gitignore b/testsuite/tests/ghc-api/annotations/.gitignore
index 2280a5a..fc9760f 100644
--- a/testsuite/tests/ghc-api/annotations/.gitignore
+++ b/testsuite/tests/ghc-api/annotations/.gitignore
@@ -6,6 +6,7 @@ listcomps
t10255
t10268
t10269
+t10280
*.hi
*.o
*.run.*
diff --git a/testsuite/tests/ghc-api/annotations/Makefile b/testsuite/tests/ghc-api/annotations/Makefile
index 898db5f..44b2889 100644
--- a/testsuite/tests/ghc-api/annotations/Makefile
+++ b/testsuite/tests/ghc-api/annotations/Makefile
@@ -44,6 +44,11 @@ T10268:
'$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc t10268
./t10268 "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`"
+T10280:
+ rm -f t10280.o t10280.hi
+ '$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc t10280
+ ./t10280 "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`"
+
.PHONY: clean annotations parseTree comments exampleTest listcomps
T10269:
diff --git a/testsuite/tests/ghc-api/annotations/T10280.stderr b/testsuite/tests/ghc-api/annotations/T10280.stderr
new file mode 100644
index 0000000..114b95b
--- /dev/null
+++ b/testsuite/tests/ghc-api/annotations/T10280.stderr
@@ -0,0 +1,6 @@
+
+Test10280.hs:4:8: Not in scope: ‘atomicModifyIORef’
+
+Test10280.hs:4:26: Not in scope: ‘ciTokens’
+
+Test10280.hs:4:44: Not in scope: ‘f’
diff --git a/testsuite/tests/ghc-api/annotations/T10280.stdout b/testsuite/tests/ghc-api/annotations/T10280.stdout
new file mode 100644
index 0000000..82a0eb2
--- /dev/null
+++ b/testsuite/tests/ghc-api/annotations/T10280.stdout
@@ -0,0 +1,36 @@
+---Problems---------------------
+[
+(AK <no location info> AnnEofPos = [Test10280.hs:5:1])
+]
+
+--------------------------------
+[
+(AK Test10280.hs:1:1 AnnModule = [Test10280.hs:2:1-6])
+
+(AK Test10280.hs:1:1 AnnWhere = [Test10280.hs:2:18-22])
+
+(AK Test10280.hs:4:1-45 AnnEqual = [Test10280.hs:4:6])
+
+(AK Test10280.hs:4:1-45 AnnFunId = [Test10280.hs:4:1-4])
+
+(AK Test10280.hs:4:1-45 AnnSemi = [Test10280.hs:5:1])
+
+(AK Test10280.hs:4:35-45 AnnCloseP = [Test10280.hs:4:45])
+
+(AK Test10280.hs:4:35-45 AnnOpenP = [Test10280.hs:4:35])
+
+(AK Test10280.hs:4:36-40 AnnCloseP = [Test10280.hs:4:40])
+
+(AK Test10280.hs:4:36-40 AnnOpenP = [Test10280.hs:4:36])
+
+(AK Test10280.hs:4:36-44 AnnVal = [Test10280.hs:4:42])
+
+(AK Test10280.hs:4:37 AnnComma = [Test10280.hs:4:37])
+
+(AK Test10280.hs:4:38-39 AnnCloseP = [Test10280.hs:4:39])
+
+(AK Test10280.hs:4:38-39 AnnOpenP = [Test10280.hs:4:38])
+
+(AK <no location info> AnnEofPos = [Test10280.hs:5:1])
+]
+
diff --git a/testsuite/tests/ghc-api/annotations/Test10280.hs b/testsuite/tests/ghc-api/annotations/Test10280.hs
new file mode 100644
index 0000000..08e4186
--- /dev/null
+++ b/testsuite/tests/ghc-api/annotations/Test10280.hs
@@ -0,0 +1,4 @@
+{-# LANGUAGE TupleSections #-}
+module Test10280 where
+
+foo2 = atomicModifyIORef ciTokens ((,()) . f)
diff --git a/testsuite/tests/ghc-api/annotations/all.T b/testsuite/tests/ghc-api/annotations/all.T
index 29e22c6..e0834af 100644
--- a/testsuite/tests/ghc-api/annotations/all.T
+++ b/testsuite/tests/ghc-api/annotations/all.T
@@ -6,3 +6,4 @@ test('listcomps', normal, run_command, ['$MAKE -s --no-print-directory listcom
test('T10255', normal, run_command, ['$MAKE -s --no-print-directory t10255'])
test('T10268', normal, run_command, ['$MAKE -s --no-print-directory T10268'])
test('T10269', normal, run_command, ['$MAKE -s --no-print-directory T10269'])
+test('T10280', normal, run_command, ['$MAKE -s --no-print-directory T10280'])
diff --git a/testsuite/tests/ghc-api/annotations/t10269.hs b/testsuite/tests/ghc-api/annotations/t10280.hs
similarity index 98%
copy from testsuite/tests/ghc-api/annotations/t10269.hs
copy to testsuite/tests/ghc-api/annotations/t10280.hs
index e71cd3b..5ed78af 100644
--- a/testsuite/tests/ghc-api/annotations/t10269.hs
+++ b/testsuite/tests/ghc-api/annotations/t10280.hs
@@ -24,7 +24,7 @@ import Data.Dynamic ( fromDynamic,Dynamic )
main::IO()
main = do
[libdir] <- getArgs
- testOneFile libdir "Test10269"
+ testOneFile libdir "Test10280"
testOneFile libdir fileName = do
((anns,cs),p) <- runGhc (Just libdir) $ do
More information about the ghc-commits
mailing list