[commit: ghc] ghc-7.10: ApiAnnotatons : AnnDcolon in wrong place for PatBind (d66eb5a)

git at git.haskell.org git at git.haskell.org
Fri May 22 13:09:36 UTC 2015


Repository : ssh://git@git.haskell.org/ghc

On branch  : ghc-7.10
Link       : http://ghc.haskell.org/trac/ghc/changeset/d66eb5a911ac5cb6d00acde326a306fcae6c6fee/ghc

>---------------------------------------------------------------

commit d66eb5a911ac5cb6d00acde326a306fcae6c6fee
Author: Alan Zimmerman <alan.zimm at gmail.com>
Date:   Thu May 21 15:48:07 2015 +0200

    ApiAnnotatons : AnnDcolon in wrong place for PatBind
    
    Summary:
    In the following code fragment
    
        let ls :: Int = undefined
    
    the `::` is attached to the ls function as a whole, rather than to the
    pattern on the LHS.
    
    Test Plan: ./validate
    
    Reviewers: hvr, austin
    
    Reviewed By: austin
    
    Subscribers: bgamari, thomie, mpickering
    
    Differential Revision: https://phabricator.haskell.org/D883
    
    GHC Trac Issues: #10396
    
    (cherry picked from commit c488da851c39ca202cdd056091176acbabdd7dd4)


>---------------------------------------------------------------

d66eb5a911ac5cb6d00acde326a306fcae6c6fee
 compiler/parser/Parser.y                           |  5 ++-
 testsuite/tests/ghc-api/annotations/.gitignore     |  1 +
 testsuite/tests/ghc-api/annotations/Makefile       |  8 ++++
 testsuite/tests/ghc-api/annotations/T10354.stderr  |  2 +-
 testsuite/tests/ghc-api/annotations/T10396.stdout  | 43 ++++++++++++++++++++++
 testsuite/tests/ghc-api/annotations/Test10396.hs   |  7 ++++
 testsuite/tests/ghc-api/annotations/all.T          |  1 +
 .../tests/ghc-api/annotations/exampleTest.stdout   |  2 +-
 .../tests/ghc-api/annotations/parseTree.stdout     |  2 +-
 .../ghc-api/annotations/{t10278.hs => t10396.hs}   |  2 +-
 10 files changed, 67 insertions(+), 6 deletions(-)

diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y
index d37c204..53a7b7c 100644
--- a/compiler/parser/Parser.y
+++ b/compiler/parser/Parser.y
@@ -1870,8 +1870,9 @@ decl_no_th :: { Located (OrdList (LHsDecl RdrName)) }
                                         case r of {
                                           (FunBind n _ _ _ _ _) ->
                                                 ams (L l ()) (mj AnnFunId n:(fst $2)) >> return () ;
-                                          _ -> return () } ;
-                                        _ <- ams (L l ()) (ann ++ (fst $2) ++ (fst $ unLoc $3));
+                                          (PatBind (L lh _lhs) _rhs _ _ _) ->
+                                                ams (L lh ()) (fst $2) >> return () } ;
+                                        _ <- ams (L l ()) (ann ++ (fst $ unLoc $3));
                                         return $! (sL l (unitOL $! (sL l $ ValD r))) } }
         | pattern_synonym_decl  { sLL $1 $> $ unitOL $1 }
         | docdecl               { sLL $1 $> $ unitOL $1 }
diff --git a/testsuite/tests/ghc-api/annotations/.gitignore b/testsuite/tests/ghc-api/annotations/.gitignore
index bb19b13..a7726f8 100644
--- a/testsuite/tests/ghc-api/annotations/.gitignore
+++ b/testsuite/tests/ghc-api/annotations/.gitignore
@@ -15,6 +15,7 @@ t10307
 boolFormula
 t10278
 t10354
+t10396
 *.hi
 *.o
 *.run.*
diff --git a/testsuite/tests/ghc-api/annotations/Makefile b/testsuite/tests/ghc-api/annotations/Makefile
index da6a358..69ce026 100644
--- a/testsuite/tests/ghc-api/annotations/Makefile
+++ b/testsuite/tests/ghc-api/annotations/Makefile
@@ -13,6 +13,7 @@ clean:
 	rm -f t10357
 	rm -f t10278
 	rm -f t10354
+	rm -f t10396
 
 annotations: 
 	rm -f annotations.o annotations.hi
@@ -46,6 +47,13 @@ t10358:
 
 .PHONY: t10358
 
+T10396:
+	rm -f T10396.o T10396.hi
+	'$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc t10396
+	./t10396 "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`"
+
+.PHONY: t10396
+
 t10255:
 	rm -f t10255.o t10255.hi
 	'$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc t10255
diff --git a/testsuite/tests/ghc-api/annotations/T10354.stderr b/testsuite/tests/ghc-api/annotations/T10354.stderr
index c0f9172..1e97b8a 100644
--- a/testsuite/tests/ghc-api/annotations/T10354.stderr
+++ b/testsuite/tests/ghc-api/annotations/T10354.stderr
@@ -1,3 +1,3 @@
 
-Test10354.hs:13:8: error:
+Test10354.hs:13:8:
     Not in scope: type constructor or class ‘ForceError’
diff --git a/testsuite/tests/ghc-api/annotations/T10396.stdout b/testsuite/tests/ghc-api/annotations/T10396.stdout
new file mode 100644
index 0000000..61d0399
--- /dev/null
+++ b/testsuite/tests/ghc-api/annotations/T10396.stdout
@@ -0,0 +1,43 @@
+---Problems---------------------
+[
+]
+
+---Problems'--------------------
+[]
+--------------------------------
+[
+(AK Test10396.hs:1:1 AnnModule = [Test10396.hs:2:1-6])
+
+(AK Test10396.hs:1:1 AnnWhere = [Test10396.hs:2:18-22])
+
+(AK Test10396.hs:4:1-15 AnnDcolon = [Test10396.hs:4:8-9])
+
+(AK Test10396.hs:4:1-15 AnnSemi = [Test10396.hs:5:1])
+
+(AK Test10396.hs:4:14-15 AnnCloseP = [Test10396.hs:4:15])
+
+(AK Test10396.hs:4:14-15 AnnOpenP = [Test10396.hs:4:14])
+
+(AK Test10396.hs:(5,1)-(7,11) AnnEqual = [Test10396.hs:5:7])
+
+(AK Test10396.hs:(5,1)-(7,11) AnnFunId = [Test10396.hs:5:1-6])
+
+(AK Test10396.hs:(5,1)-(7,11) AnnSemi = [Test10396.hs:8:1])
+
+(AK Test10396.hs:(5,9)-(7,11) AnnDo = [Test10396.hs:5:9-10])
+
+(AK Test10396.hs:6:3-27 AnnLet = [Test10396.hs:6:3-5])
+
+(AK Test10396.hs:6:3-27 AnnSemi = [Test10396.hs:7:3])
+
+(AK Test10396.hs:6:7-15 AnnDcolon = [Test10396.hs:6:10-11])
+
+(AK Test10396.hs:6:7-27 AnnEqual = [Test10396.hs:6:17])
+
+(AK Test10396.hs:7:10-11 AnnCloseP = [Test10396.hs:7:11])
+
+(AK Test10396.hs:7:10-11 AnnOpenP = [Test10396.hs:7:10])
+
+(AK <no location info> AnnEofPos = [Test10396.hs:8:1])
+]
+
diff --git a/testsuite/tests/ghc-api/annotations/Test10396.hs b/testsuite/tests/ghc-api/annotations/Test10396.hs
new file mode 100644
index 0000000..71b18a8
--- /dev/null
+++ b/testsuite/tests/ghc-api/annotations/Test10396.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE ScopedTypeVariables #-}
+module Test10396 where
+
+errors :: IO ()
+errors= do
+  let ls :: Int = undefined
+  return ()
diff --git a/testsuite/tests/ghc-api/annotations/all.T b/testsuite/tests/ghc-api/annotations/all.T
index 0a0b5a6..ed04646 100644
--- a/testsuite/tests/ghc-api/annotations/all.T
+++ b/testsuite/tests/ghc-api/annotations/all.T
@@ -15,3 +15,4 @@ test('T10357',      normal, run_command, ['$MAKE -s --no-print-directory t10357'
 test('T10358',      normal, run_command, ['$MAKE -s --no-print-directory t10358'])
 test('T10278',      normal, run_command, ['$MAKE -s --no-print-directory T10278'])
 test('T10354',      normal, run_command, ['$MAKE -s --no-print-directory T10354'])
+test('T10396',      normal, run_command, ['$MAKE -s --no-print-directory T10396'])
diff --git a/testsuite/tests/ghc-api/annotations/exampleTest.stdout b/testsuite/tests/ghc-api/annotations/exampleTest.stdout
index 128b70a..706d858 100644
--- a/testsuite/tests/ghc-api/annotations/exampleTest.stdout
+++ b/testsuite/tests/ghc-api/annotations/exampleTest.stdout
@@ -149,7 +149,7 @@
 
 (AK AnnotationTuple.hs:23:9-24 AnnLarrow = [AnnotationTuple.hs:23:16-17])
 
-(AK AnnotationTuple.hs:26:1-14 AnnDcolon = [AnnotationTuple.hs:26:5-6])
+(AK AnnotationTuple.hs:26:1-10 AnnDcolon = [AnnotationTuple.hs:26:5-6])
 
 (AK AnnotationTuple.hs:26:1-14 AnnEqual = [AnnotationTuple.hs:26:12])
 
diff --git a/testsuite/tests/ghc-api/annotations/parseTree.stdout b/testsuite/tests/ghc-api/annotations/parseTree.stdout
index 9965fd2..4986ddf 100644
--- a/testsuite/tests/ghc-api/annotations/parseTree.stdout
+++ b/testsuite/tests/ghc-api/annotations/parseTree.stdout
@@ -153,7 +153,7 @@
 
 (AK AnnotationTuple.hs:23:9-24 AnnLarrow = [AnnotationTuple.hs:23:16-17])
 
-(AK AnnotationTuple.hs:26:1-14 AnnDcolon = [AnnotationTuple.hs:26:5-6])
+(AK AnnotationTuple.hs:26:1-10 AnnDcolon = [AnnotationTuple.hs:26:5-6])
 
 (AK AnnotationTuple.hs:26:1-14 AnnEqual = [AnnotationTuple.hs:26:12])
 
diff --git a/testsuite/tests/ghc-api/annotations/t10278.hs b/testsuite/tests/ghc-api/annotations/t10396.hs
similarity index 98%
copy from testsuite/tests/ghc-api/annotations/t10278.hs
copy to testsuite/tests/ghc-api/annotations/t10396.hs
index 9d13548..5ece668 100644
--- a/testsuite/tests/ghc-api/annotations/t10278.hs
+++ b/testsuite/tests/ghc-api/annotations/t10396.hs
@@ -24,7 +24,7 @@ import Data.Dynamic ( fromDynamic,Dynamic )
 main::IO()
 main = do
         [libdir] <- getArgs
-        testOneFile libdir "Test10278"
+        testOneFile libdir "Test10396"
 
 testOneFile libdir fileName = do
        ((anns,cs),p) <- runGhc (Just libdir) $ do



More information about the ghc-commits mailing list