[commit: ghc] master: check-ppr: Add a --dump flag to aid in debugging (5c76f83)
git at git.haskell.org
git at git.haskell.org
Thu Dec 15 15:43:40 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/5c76f834b5b7f2ee9712d0888a8b1b186b77dee5/ghc
>---------------------------------------------------------------
commit 5c76f834b5b7f2ee9712d0888a8b1b186b77dee5
Author: Ben Gamari <ben at smart-cactus.org>
Date: Wed Dec 14 17:09:02 2016 -0500
check-ppr: Add a --dump flag to aid in debugging
Currently tracking down where two ASTs disagree is quite difficult. Add a --dump
flag to check-ppr which dumps the respective ASTs to files, which can then be
easily compared with diff, etc.
>---------------------------------------------------------------
5c76f834b5b7f2ee9712d0888a8b1b186b77dee5
utils/check-ppr/Main.hs | 26 +++++++++++++++++++++-----
utils/check-ppr/README | 3 +++
2 files changed, 24 insertions(+), 5 deletions(-)
diff --git a/utils/check-ppr/Main.hs b/utils/check-ppr/Main.hs
index c61b0e6..8c93769 100644
--- a/utils/check-ppr/Main.hs
+++ b/utils/check-ppr/Main.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RankNTypes #-}
+import Control.Monad (when)
import Data.Data hiding (Fixity)
import Data.List
import Bag
@@ -20,15 +21,27 @@ import System.FilePath
import qualified Data.ByteString as B
import qualified Data.Map as Map
-main::IO()
+usage :: String
+usage = unlines
+ [ "usage: check-ppr [--dump] (libdir) (file)"
+ , ""
+ , "where libdir is the GHC library directory (e.g. the output of"
+ , "ghc --print-libdir) and file is the file to parse."
+ , "The --dump flag causes check-ppr to produce .new and .old files"
+ , "containing dumps of the new and old ASTs in the event of a match"
+ , "failure."
+ ]
+
+main :: IO()
main = do
args <- getArgs
case args of
- [libdir,fileName] -> testOneFile libdir fileName
- _ -> putStrLn "invoke with the libdir and a file to parse."
+ [libdir,fileName] -> testOneFile libdir fileName False
+ ["--dump", libdir,fileName] -> testOneFile libdir fileName True
+ _ -> putStrLn usage
-testOneFile :: FilePath -> String -> IO ()
-testOneFile libdir fileName = do
+testOneFile :: FilePath -> String -> Bool -> IO ()
+testOneFile libdir fileName dumpOldNew = do
p <- parseOneFile libdir fileName
let
origAst = showAstData 0 (pm_parsed_source p)
@@ -56,6 +69,9 @@ testOneFile libdir fileName = do
putStrLn origAst
putStrLn "\n===================================\nNew\n\n"
putStrLn newAstStr
+ when dumpOldNew $ do
+ writeFile (fileName <.> "old") origAst
+ writeFile (fileName <.> "new") newAstStr
exitFailure
diff --git a/utils/check-ppr/README b/utils/check-ppr/README
index ac0eb55..d31442a 100644
--- a/utils/check-ppr/README
+++ b/utils/check-ppr/README
@@ -18,3 +18,6 @@ In a test Makefile
$(CHECK_PPR) "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" FileToParse.hs
See examples in (REPO_HOME)/testsuite/tests/printer/Makefile
+
+If passed the --dump flag check-ppr will produce .new and .old files containing
+the ASTs before and after round-tripping to aid debugging.
More information about the ghc-commits
mailing list