diff options
author | Ben Gamari <bgamari.foss@gmail.com> | 2017-09-27 15:22:37 -0400 |
---|---|---|
committer | Ben Gamari <ben@smart-cactus.org> | 2017-09-27 17:37:29 -0400 |
commit | 1e9f90af7311c33de0f7f5b7dba594725596d675 (patch) | |
tree | 705865c81d93f3084934825917eadb4e42296fac /utils/check-api-annotations | |
parent | 4364f1e7543b6803cfaef321105d253e0bdf08a4 (diff) | |
download | haskell-1e9f90af7311c33de0f7f5b7dba594725596d675.tar.gz |
Move check-ppr and check-api-annotations to testsuite/utils
These are needed by the testsuite and consequently must be shipped in
the testsuite tarball to ensure that we can test binary distributions.
See #13897.
Test Plan: Validate
Reviewers: austin
Subscribers: snowleopard, rwbarton, thomie
GHC Trac Issues: #13897
Differential Revision: https://phabricator.haskell.org/D4039
Diffstat (limited to 'utils/check-api-annotations')
-rw-r--r-- | utils/check-api-annotations/Main.hs | 122 | ||||
-rw-r--r-- | utils/check-api-annotations/README | 103 | ||||
-rw-r--r-- | utils/check-api-annotations/check-api-annotations.cabal | 29 | ||||
-rw-r--r-- | utils/check-api-annotations/ghc.mk | 18 |
4 files changed, 0 insertions, 272 deletions
diff --git a/utils/check-api-annotations/Main.hs b/utils/check-api-annotations/Main.hs deleted file mode 100644 index 6b973e12e8..0000000000 --- a/utils/check-api-annotations/Main.hs +++ /dev/null @@ -1,122 +0,0 @@ -{-# LANGUAGE RankNTypes #-} - -import Data.Data -import Data.List -import GHC -import DynFlags -import Outputable -import ApiAnnotation -import System.Environment( getArgs ) -import System.Exit -import qualified Data.Map as Map -import qualified Data.Set as Set - -main::IO() -main = do - args <- getArgs - case args of - [libdir,fileName] -> testOneFile libdir fileName - _ -> putStrLn "invoke with the libdir and a file to parse." - -testOneFile :: FilePath -> String -> IO () -testOneFile libdir fileName = do - let modByFile m = - case ml_hs_file $ ms_location m of - Nothing -> False - Just fn -> fn == fileName - ((anns,_cs),p) <- runGhc (Just libdir) $ do - dflags <- getSessionDynFlags - _ <- setSessionDynFlags dflags - addTarget Target { targetId = TargetFile fileName Nothing - , targetAllowObjCode = True - , targetContents = Nothing } - _ <- load LoadAllTargets - graph <- getModuleGraph - let modSum = - case filter modByFile (mgModSummaries graph) of - [x] -> x - xs -> error $ "Can't find module, got:" - ++ show (map (ml_hs_file . ms_location) xs) - p <- parseModule modSum - return (pm_annotations p,p) - - let sspans = Set.fromList $ getAllSrcSpans (pm_parsed_source p) - - 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 sspans) anchors)) - exploded' - - problems'' = filter (\((a,_),_) -> a /= AnnEofPos) problems' - - putStrLn "---Problems (should be empty list)---" - putStrLn (intercalate "\n" [pp $ Map.fromList $ map fst problems'']) - putStrLn "---Annotations-----------------------" - putStrLn "-- SrcSpan the annotation is attached to, AnnKeywordId," - putStrLn "-- list of locations the keyword item appears in" - -- putStrLn (intercalate "\n" [showAnns anns]) - putStrLn (showAnns anns) - if null problems'' - then exitSuccess - else exitFailure - - where - getAllSrcSpans :: (Data t) => t -> [SrcSpan] - getAllSrcSpans ast = everything (++) ([] `mkQ` getSrcSpan) ast - where - getSrcSpan :: SrcSpan -> [SrcSpan] - getSrcSpan ss = [ss] - - -showAnns :: Map.Map ApiAnnKey [SrcSpan] -> String -showAnns anns = "[\n" ++ (intercalate ",\n" - $ map (\((s,k),v) - -- -> ("(AK " ++ pp s ++ " " ++ show k ++" = " ++ pp v ++ ")\n")) - -> ("((" ++ pp s ++ "," ++ show k ++"), " ++ pp v ++ ")")) - $ Map.toList anns) - ++ "\n]\n" - -pp :: (Outputable a) => a -> String -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) diff --git a/utils/check-api-annotations/README b/utils/check-api-annotations/README deleted file mode 100644 index fcadc50ff6..0000000000 --- a/utils/check-api-annotations/README +++ /dev/null @@ -1,103 +0,0 @@ -This programme is intended to be used by any GHC developers working on Parser.y -or RdrHsSyn.hs, and who want to check that their changes do not break the API -Annotations. - -It does a basic test that all annotations do make it to the final AST, and dumps -a list of the annotations generated for a given file, so that they can be -checked against the source being parsed for sanity. - -This utility is also intended to be used in tests, so that when new features are -added the expected annotations are also captured. - -Usage - -In a test Makefile - - $(CHECK_API_ANNOTATIONS) "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" FileToParse.hs - -See examples in (REPO_HOME)/testsuite/tests/ghc-api/annotations/Makefile - - -Description of operation ------------------------- - -The programme is called with the name of a haskell source file. - -It uses the GHC API to load and parse this, and extracts the API annotations. - -These are of the form - - Map.Map ApiAnnKey [SrcSpan] - -where - - type ApiAnnKey = (SrcSpan,AnnKeywordId) - -So an annotation is a key comprising the parent SrcSpan in the ParsedSource -together with an AnnKeywordId, and this maps to a list of locations where the -specific keyword item occurs in the original source. - -The utility extracts all SrcSpans in the ParsedSource, and makes sure that for -every ApiAnnKey the SrcSpan is actually present in the final ParsedSource. This -is to ensure that when a given parser production is postprocessed anywhere along -the line the relevant SrcSpan is not discarded, thus detaching the annotation -from the final output. - -It also provides a list of each ApiAnnKey and the corresponding source -locations, so these can be checked against the original source for correctness. - -Example -------- - -Test10255.hs in the ghc-api/annotations tests has the following source - ------------------------------- -1:{-# LANGUAGE ScopedTypeVariables #-} -2:module Test10255 where -3: -4:import Data.Maybe -5: -6:fob (f :: (Maybe t -> Int)) = -7: undefined ------------------------------- - -The output of this utility is - ------------------------------------------------------------------------- ----Problems (should be empty list)--- -[] ----Annotations----------------------- --- SrcSpan the annotation is attached to, AnnKeywordId, --- list of locations the keyword item appears in -[ -((Test10255.hs:1:1,AnnModule), [Test10255.hs:2:1-6]), -((Test10255.hs:1:1,AnnWhere), [Test10255.hs:2:18-22]), -((Test10255.hs:4:1-17,AnnImport), [Test10255.hs:4:1-6]), -((Test10255.hs:4:1-17,AnnSemi), [Test10255.hs:6:1]), -((Test10255.hs:(6,1)-(7,11),AnnEqual), [Test10255.hs:6:29]), -((Test10255.hs:(6,1)-(7,11),AnnFunId), [Test10255.hs:6:1-3]), -((Test10255.hs:(6,1)-(7,11),AnnSemi), [Test10255.hs:8:1]), -((Test10255.hs:6:5-27,AnnCloseP), [Test10255.hs:6:27]), -((Test10255.hs:6:5-27,AnnOpenP), [Test10255.hs:6:5]), -((Test10255.hs:6:6-26,AnnDcolon), [Test10255.hs:6:8-9]), -((Test10255.hs:6:11-26,AnnCloseP), [Test10255.hs:6:26]), -((Test10255.hs:6:11-26,AnnOpenP), [Test10255.hs:6:11]), -((Test10255.hs:6:12-18,AnnRarrow), [Test10255.hs:6:20-21]), -((Test10255.hs:6:12-25,AnnRarrow), [Test10255.hs:6:20-21]), -((<no location info>,AnnEofPos), [Test10255.hs:8:1]) -] ------------------------------------------------------------------------- - -To interpret this, firstly the problems list is empty, so there are not -annotations that do not appear in the final AST. - -Secondly, the list of annotations and locations can be checked against the test -source code to ensure that every AnnKeywordId does in fact appear. - -It will return a zero exit code if the list of problems is empty, non-zero -otherwise. - -Note: In some cases, such as T10269 in the ghc-api/annotations tests the list is -non-empty, due to postprocessing of the parsed result. In general this should -only happen for an `AnnVal` and if it does the actual annotations provided need -to be inspected to check that an equivalent annotation is provided. diff --git a/utils/check-api-annotations/check-api-annotations.cabal b/utils/check-api-annotations/check-api-annotations.cabal deleted file mode 100644 index 880f4d6603..0000000000 --- a/utils/check-api-annotations/check-api-annotations.cabal +++ /dev/null @@ -1,29 +0,0 @@ -Name: check-api-annotations -Version: 0.1 -Copyright: XXX -License: BSD3 --- XXX License-File: LICENSE -Author: XXX -Maintainer: XXX -Synopsis: A utilities for checking the consistency of GHC's API annotations. -Description: - This utility is used to check the consistency between GHC's syntax tree - and API annotations used to track token-level details of the original - source file. See @utils/check-api-annotations/README@ in GHC's source - distribution for details. -Category: Development -build-type: Simple -cabal-version: >=1.10 - -Executable check-api-annotations - Default-Language: Haskell2010 - - Main-Is: Main.hs - - Ghc-Options: -Wall - - Build-Depends: base >= 4 && < 5, - containers, - Cabal >= 2.0 && < 2.1, - directory, - ghc diff --git a/utils/check-api-annotations/ghc.mk b/utils/check-api-annotations/ghc.mk deleted file mode 100644 index 61f896d3d7..0000000000 --- a/utils/check-api-annotations/ghc.mk +++ /dev/null @@ -1,18 +0,0 @@ -# ----------------------------------------------------------------------------- -# -# (c) 2009 The University of Glasgow -# -# This file is part of the GHC build system. -# -# To understand how the build system works and how to modify it, see -# http://ghc.haskell.org/trac/ghc/wiki/Building/Architecture -# http://ghc.haskell.org/trac/ghc/wiki/Building/Modifying -# -# ----------------------------------------------------------------------------- - -utils/check-api-annotations_USES_CABAL = YES -utils/check-api-annotations_PACKAGE = check-api-annotations -utils/check-api-annotations_dist-install_PROGNAME = check-api-annotations -utils/check-api-annotations_dist-install_INSTALL = NO -utils/check-api-annotations_dist-install_INSTALL_INPLACE = YES -$(eval $(call build-prog,utils/check-api-annotations,dist-install,2)) |