Added normalize funcion to latex citation tests.
This is necessary because converting from markdown to latex correctly changes hyphens to en-dashes and some spaces to non-breaking spaces. Converting back to markdown does not undo this changes, and so the tests have to undo them.
This commit is contained in:
parent
3ac6f72f98
commit
53cb199bab
1 changed files with 21 additions and 9 deletions
|
@ -21,6 +21,7 @@ import System.Environment
|
||||||
import System.Exit
|
import System.Exit
|
||||||
import Text.Printf
|
import Text.Printf
|
||||||
import Data.Algorithm.Diff
|
import Data.Algorithm.Diff
|
||||||
|
import Data.String.Utils ( replace )
|
||||||
import Prelude hiding ( readFile )
|
import Prelude hiding ( readFile )
|
||||||
import qualified Data.ByteString.Lazy as B
|
import qualified Data.ByteString.Lazy as B
|
||||||
import Data.ByteString.Lazy.UTF8 (toString, fromString)
|
import Data.ByteString.Lazy.UTF8 (toString, fromString)
|
||||||
|
@ -166,7 +167,8 @@ runLatexCitationTests o n
|
||||||
where
|
where
|
||||||
o' = o ++ ["--" ++ n]
|
o' = o ++ ["--" ++ n]
|
||||||
f = n ++ "-citations.latex"
|
f = n ++ "-citations.latex"
|
||||||
rt = runTest
|
normalize = replace "\160" " " . replace "\8211" "-"
|
||||||
|
rt = runTestWithNormalize normalize
|
||||||
|
|
||||||
runWriterTest :: String -> IO Bool
|
runWriterTest :: String -> IO Bool
|
||||||
runWriterTest format = do
|
runWriterTest format = do
|
||||||
|
@ -178,13 +180,23 @@ runS5WriterTest :: String -> [String] -> String -> IO Bool
|
||||||
runS5WriterTest modifier opts format = runTest (format ++ " writer (" ++ modifier ++ ")")
|
runS5WriterTest modifier opts format = runTest (format ++ " writer (" ++ modifier ++ ")")
|
||||||
(["-r", "native", "-w", format] ++ opts) "s5.native" ("s5." ++ modifier <.> "html")
|
(["-r", "native", "-w", format] ++ opts) "s5.native" ("s5." ++ modifier <.> "html")
|
||||||
|
|
||||||
-- | Run a test, return True if test passed.
|
|
||||||
runTest :: String -- ^ Title of test
|
-- | Run a test without normalize function, return True if test passed.
|
||||||
-> [String] -- ^ Options to pass to pandoc
|
runTest :: String -- ^ Title of test
|
||||||
-> String -- ^ Input filepath
|
-> [String] -- ^ Options to pass to pandoc
|
||||||
-> FilePath -- ^ Norm (for test results) filepath
|
-> String -- ^ Input filepath
|
||||||
-> IO Bool
|
-> FilePath -- ^ Norm (for test results) filepath
|
||||||
runTest testname opts inp norm = do
|
-> IO Bool
|
||||||
|
runTest = runTestWithNormalize id
|
||||||
|
|
||||||
|
-- | Run a test with normalize function, return True if test passed.
|
||||||
|
runTestWithNormalize :: (String -> String) -- ^ Normalize function for output
|
||||||
|
-> String -- ^ Title of test
|
||||||
|
-> [String] -- ^ Options to pass to pandoc
|
||||||
|
-> String -- ^ Input filepath
|
||||||
|
-> FilePath -- ^ Norm (for test results) filepath
|
||||||
|
-> IO Bool
|
||||||
|
runTestWithNormalize normalize testname opts inp norm = do
|
||||||
putStr $ printf "%-28s ---> " testname
|
putStr $ printf "%-28s ---> " testname
|
||||||
(outputPath, hOut) <- openTempFile "" "pandoc-test"
|
(outputPath, hOut) <- openTempFile "" "pandoc-test"
|
||||||
let inpPath = inp
|
let inpPath = inp
|
||||||
|
@ -197,7 +209,7 @@ runTest testname opts inp norm = do
|
||||||
result <- if ec == ExitSuccess
|
result <- if ec == ExitSuccess
|
||||||
then do
|
then do
|
||||||
-- filter \r so the tests will work on Windows machines
|
-- filter \r so the tests will work on Windows machines
|
||||||
outputContents <- readFile' outputPath >>= return . filter (/='\r')
|
outputContents <- readFile' outputPath >>= return . filter (/='\r') . normalize
|
||||||
normContents <- readFile' normPath >>= return . filter (/='\r')
|
normContents <- readFile' normPath >>= return . filter (/='\r')
|
||||||
if outputContents == normContents
|
if outputContents == normContents
|
||||||
then return TestPassed
|
then return TestPassed
|
||||||
|
|
Loading…
Add table
Reference in a new issue