Skip to content
Snippets Groups Projects
Commit 5c76f834 authored by Ben Gamari's avatar Ben Gamari
Browse files

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.
parent 2940a617
No related branches found
No related tags found
No related merge requests found
{-# 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
......
......@@ -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.
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment