summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAlan Zimmerman <alan.zimm@gmail.com>2015-05-21 15:48:07 +0200
committerAlan Zimmerman <alan.zimm@gmail.com>2015-05-21 20:24:41 +0200
commit382eba2bbad73b6dcfb8d0bad3bb2d6cc0ded5a3 (patch)
treee7d5156773f13acc134926451583f21b24f70cd3
parent1289c598b91ba3ec7c5313cc20437a41122c1fc2 (diff)
downloadhaskell-wip/api-annots-ghc-7.10.tar.gz
ApiAnnotatons : AnnDcolon in wrong place for PatBindwip/api-annots-ghc-7.10
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)
-rw-r--r--compiler/parser/Parser.y5
-rw-r--r--testsuite/tests/ghc-api/annotations/.gitignore1
-rw-r--r--testsuite/tests/ghc-api/annotations/Makefile8
-rw-r--r--testsuite/tests/ghc-api/annotations/T10354.stderr2
-rw-r--r--testsuite/tests/ghc-api/annotations/T10396.stdout43
-rw-r--r--testsuite/tests/ghc-api/annotations/Test10396.hs7
-rw-r--r--testsuite/tests/ghc-api/annotations/all.T1
-rw-r--r--testsuite/tests/ghc-api/annotations/exampleTest.stdout2
-rw-r--r--testsuite/tests/ghc-api/annotations/parseTree.stdout2
-rw-r--r--testsuite/tests/ghc-api/annotations/t10396.hs118
10 files changed, 184 insertions, 5 deletions
diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y
index d37c2045ec..53a7b7c8d0 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 bb19b136c0..a7726f8722 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 da6a3586d7..69ce026d66 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 c0f9172c02..1e97b8a2f2 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 0000000000..61d03994c8
--- /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 0000000000..71b18a8f9e
--- /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 0a0b5a6b7d..ed046465d5 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 128b70a598..706d858df2 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 9965fd21b1..4986ddfa6d 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/t10396.hs b/testsuite/tests/ghc-api/annotations/t10396.hs
new file mode 100644
index 0000000000..5ece668d61
--- /dev/null
+++ b/testsuite/tests/ghc-api/annotations/t10396.hs
@@ -0,0 +1,118 @@
+{-# LANGUAGE RankNTypes #-}
+
+-- This program must be called with GHC's libdir as the single command line
+-- argument.
+module Main where
+
+-- import Data.Generics
+import Data.Data
+import Data.List
+import System.IO
+import GHC
+import BasicTypes
+import DynFlags
+import MonadUtils
+import Outputable
+import ApiAnnotation
+import Bag (filterBag,isEmptyBag)
+import System.Directory (removeFile)
+import System.Environment( getArgs )
+import qualified Data.Map as Map
+import qualified Data.Set as Set
+import Data.Dynamic ( fromDynamic,Dynamic )
+
+main::IO()
+main = do
+ [libdir] <- getArgs
+ testOneFile libdir "Test10396"
+
+testOneFile libdir fileName = do
+ ((anns,cs),p) <- runGhc (Just libdir) $ do
+ dflags <- getSessionDynFlags
+ setSessionDynFlags dflags
+ let mn =mkModuleName fileName
+ addTarget Target { targetId = TargetModule mn
+ , targetAllowObjCode = True
+ , targetContents = Nothing }
+ load LoadAllTargets
+ modSum <- getModSummary mn
+ p <- parseModule modSum
+ return (pm_annotations p,p)
+
+ let spans = Set.fromList $ getAllSrcSpans (pm_parsed_source p)
+
+ problems = filter (\(s,a) -> not (Set.member s spans))
+ $ getAnnSrcSpans (anns,cs)
+
+ exploded = [((kw,ss),[anchor])
+ | ((anchor,kw),sss) <- Map.toList anns,ss <- sss]
+
+ exploded' = Map.toList $ Map.fromListWith (++) exploded
+
+ problems' = filter (\(_,anchors)
+ -> not (any (\a -> Set.member a spans) anchors))
+ exploded'
+
+ putStrLn "---Problems---------------------"
+ putStrLn (intercalate "\n" [showAnns $ Map.fromList $ map snd problems])
+ putStrLn "---Problems'--------------------"
+ putStrLn (intercalate "\n" [pp $ Map.fromList $ map fst problems'])
+ putStrLn "--------------------------------"
+ putStrLn (intercalate "\n" [showAnns anns])
+
+ where
+ getAnnSrcSpans :: ApiAnns -> [(SrcSpan,(ApiAnnKey,[SrcSpan]))]
+ getAnnSrcSpans (anns,_) = map (\a@((ss,_),_) -> (ss,a)) $ Map.toList anns
+
+ getAllSrcSpans :: (Data t) => t -> [SrcSpan]
+ getAllSrcSpans ast = everything (++) ([] `mkQ` getSrcSpan) ast
+ where
+ getSrcSpan :: SrcSpan -> [SrcSpan]
+ getSrcSpan ss = [ss]
+
+
+showAnns anns = "[\n" ++ (intercalate "\n"
+ $ map (\((s,k),v)
+ -> ("(AK " ++ pp s ++ " " ++ show k ++" = " ++ pp v ++ ")\n"))
+ $ Map.toList anns)
+ ++ "]\n"
+
+pp a = showPpr unsafeGlobalDynFlags a
+
+
+-- ---------------------------------------------------------------------
+
+-- Copied from syb for the test
+
+
+-- | Generic queries of type \"r\",
+-- i.e., take any \"a\" and return an \"r\"
+--
+type GenericQ r = forall a. Data a => a -> r
+
+
+-- | Make a generic query;
+-- start from a type-specific case;
+-- return a constant otherwise
+--
+mkQ :: ( Typeable a
+ , Typeable b
+ )
+ => r
+ -> (b -> r)
+ -> a
+ -> r
+(r `mkQ` br) a = case cast a of
+ Just b -> br b
+ Nothing -> r
+
+
+
+-- | Summarise all nodes in top-down, left-to-right order
+everything :: (r -> r -> r) -> GenericQ r -> GenericQ r
+
+-- Apply f to x to summarise top-level node;
+-- use gmapQ to recurse into immediate subterms;
+-- use ordinary foldl to reduce list of intermediate results
+
+everything k f x = foldl k (f x) (gmapQ (everything k f) x)