Skip to content
Snippets Groups Projects
Commit adf93721 authored by GHC GitLab CI's avatar GHC GitLab CI Committed by Marge Bot
Browse files

check-ppr,check-exact: Write out result as binary

Previously we would use `writeFile` to write the intermediate files to
check for round-tripping. However, this will open the output handle as a
text handle, which on Windows will change line endings. Avoid this by
opening as binary.

Explicitly use utf8 encoding.

This is for tests only, do not need to worry about user compatibility.
parent 95275a5f
No related branches found
No related tags found
No related merge requests found
......@@ -13,6 +13,7 @@ import GHC.Hs.Dump
import System.Environment( getArgs )
import System.Exit
import System.FilePath
import System.IO
import ExactPrint
-- exactPrint = undefined
-- showPprUnsafe = undefined
......@@ -61,7 +62,7 @@ _tt = testOneFile "/home/alanz/mysrc/git.haskell.org/worktree/exactprint/_build/
-- "../../testsuite/tests/printer/Ppr033.hs"
-- "../../testsuite/tests/printer/Ppr034.hs"
-- "../../testsuite/tests/printer/Ppr035.hs"
-- "../../testsuite/tests/printer/Ppr036.hs"
"../../testsuite/tests/printer/Ppr036.hs"
-- "../../testsuite/tests/printer/Ppr037.hs"
-- "../../testsuite/tests/printer/Ppr038.hs"
-- "../../testsuite/tests/printer/Ppr039.hs"
......@@ -126,7 +127,7 @@ _tt = testOneFile "/home/alanz/mysrc/git.haskell.org/worktree/exactprint/_build/
-- "../../testsuite/tests/printer/PprRecordDotSyntax2.hs"
-- "../../testsuite/tests/printer/PprRecordDotSyntax3.hs"
-- "../../testsuite/tests/printer/PprRecordDotSyntax4.hs"
"../../testsuite/tests/printer/PprRecordDotSyntaxA.hs"
-- "../../testsuite/tests/printer/PprRecordDotSyntaxA.hs"
-- "./cases/Windows.hs"
-- exact = ppr
......@@ -148,6 +149,9 @@ main = do
[libdir,fileName] -> testOneFile libdir fileName
_ -> putStrLn usage
writeBinFile :: FilePath -> String -> IO()
writeBinFile fpath x = withBinaryFile fpath WriteMode (\h -> hSetEncoding h utf8 >> hPutStr h x)
testOneFile :: FilePath -> String -> IO ()
testOneFile libdir fileName = do
p <- parseOneFile libdir fileName
......@@ -166,9 +170,9 @@ testOneFile libdir fileName = do
newAstFile = fileName <.> "ast.new"
-- putStrLn $ "\n\nabout to writeFile"
writeFile astFile origAst
writeBinFile astFile origAst
-- putStrLn $ "\n\nabout to pp"
writeFile newFile pped
writeBinFile newFile pped
-- putStrLn $ "anns':" ++ showPprUnsafe (apiAnnRogueComments anns')
......@@ -178,7 +182,7 @@ testOneFile libdir fileName = do
newAstStr = showSDocUnsafe
$ showAstData BlankSrcSpanFile NoBlankApiAnnotations
(pm_parsed_source p')
writeFile newAstFile newAstStr
writeBinFile newAstFile newAstStr
-- putStrLn $ "\n\nanns':" ++ showPprUnsafe (apiAnnRogueComments anns')
......
......@@ -14,6 +14,7 @@ import GHC.Utils.Outputable hiding (space)
import System.Environment( getArgs )
import System.Exit
import System.FilePath
import System.IO
usage :: String
usage = unlines
......@@ -30,6 +31,12 @@ main = do
[libdir,fileName] -> testOneFile libdir fileName
_ -> putStrLn usage
-- | N.B. It's important that we write our output as binary lest Windows will
-- change our LF line endings to CRLF, which will show up in the AST when we
-- re-parse.
writeBinFile :: FilePath -> String -> IO()
writeBinFile fpath x = withBinaryFile fpath WriteMode (\h -> hSetEncoding h utf8 >> hPutStr h x)
testOneFile :: FilePath -> String -> IO ()
testOneFile libdir fileName = do
p <- parseOneFile libdir fileName
......@@ -45,8 +52,8 @@ testOneFile libdir fileName = do
astFile = fileName <.> "ast"
newAstFile = fileName <.> "ast.new"
writeFile astFile origAst
writeFile newFile pped
writeBinFile astFile origAst
writeBinFile newFile pped
p' <- parseOneFile libdir newFile
......@@ -54,7 +61,7 @@ testOneFile libdir fileName = do
newAstStr = showPprUnsafe
$ showAstData BlankSrcSpan BlankApiAnnotations
$ eraseLayoutInfo (pm_parsed_source p')
writeFile newAstFile newAstStr
writeBinFile newAstFile newAstStr
if origAst == newAstStr
then do
......
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