summaryrefslogtreecommitdiff
path: root/testsuite/tests/ghc-api
diff options
context:
space:
mode:
authorAlan Zimmerman <alan.zimm@gmail.com>2015-05-08 09:38:39 +0200
committerAlan Zimmerman <alan.zimm@gmail.com>2015-05-08 09:38:39 +0200
commit225df19a87d8de8245db84d558618f4824631acc (patch)
treee454eed3d69cfb80fd4e374194f7c375bd5d66a5 /testsuite/tests/ghc-api
parentcc9b788e701f4bd3b97bfaec8ee78169ede0fa49 (diff)
downloadhaskell-225df19a87d8de8245db84d558618f4824631acc.tar.gz
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
Diffstat (limited to 'testsuite/tests/ghc-api')
-rw-r--r--testsuite/tests/ghc-api/annotations/.gitignore1
-rw-r--r--testsuite/tests/ghc-api/annotations/Makefile5
-rw-r--r--testsuite/tests/ghc-api/annotations/T10280.stderr6
-rw-r--r--testsuite/tests/ghc-api/annotations/T10280.stdout36
-rw-r--r--testsuite/tests/ghc-api/annotations/Test10280.hs4
-rw-r--r--testsuite/tests/ghc-api/annotations/all.T1
-rw-r--r--testsuite/tests/ghc-api/annotations/t10280.hs107
7 files changed, 160 insertions, 0 deletions
diff --git a/testsuite/tests/ghc-api/annotations/.gitignore b/testsuite/tests/ghc-api/annotations/.gitignore
index 2280a5a7a8..fc9760fb89 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 898db5f248..44b28891cb 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 0000000000..114b95bd5d
--- /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 0000000000..82a0eb20ce
--- /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 0000000000..08e4186715
--- /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 29e22c6d46..e0834af10e 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/t10280.hs b/testsuite/tests/ghc-api/annotations/t10280.hs
new file mode 100644
index 0000000000..5ed78af27b
--- /dev/null
+++ b/testsuite/tests/ghc-api/annotations/t10280.hs
@@ -0,0 +1,107 @@
+{-# 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 "Test10280"
+
+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)
+
+ -- putStrLn (pp spans)
+ problems = filter (\(s,a) -> not (Set.member s spans))
+ $ getAnnSrcSpans (anns,cs)
+ putStrLn "---Problems---------------------"
+ putStrLn (intercalate "\n" [showAnns $ Map.fromList $ map snd 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)