From d86c01795f24e014ceff9420044b15600cb1f01a Mon Sep 17 00:00:00 2001 From: fiddlosopher Date: Thu, 31 Dec 2009 01:08:30 +0000 Subject: Changed RunTests.hs to use the Diff library. Previously a copy of Diff.hs was included. But it is better to use the compiled, installed version, since speed can be a problem in some cases. This change means that 'cabal test' presupposes that the Diff library is installed. Removed tests/Diff.hs from cabal file. Changed RunTests to use local environment. We need at least HOME, so pandoc can find its data directory. git-svn-id: https://pandoc.googlecode.com/svn/trunk@1672 788f1e2b-df1e-0410-8736-df70ead52e1b --- pandoc.cabal | 1 - tests/Diff.hs | 76 ------------------------------------------------------- tests/RunTests.hs | 14 +++++++--- 3 files changed, 10 insertions(+), 81 deletions(-) delete mode 100644 tests/Diff.hs diff --git a/pandoc.cabal b/pandoc.cabal index d441e6f55..cd5e6bbe0 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -126,7 +126,6 @@ Extra-Source-Files: tests/lhs-test.html, tests/lhs-test.html+lhs, tests/lhs-test.fragment.html+lhs, - tests/Diff.hs, tests/RunTests.hs Extra-Tmp-Files: man/man1/pandoc.1, man/man1/hsmarkdown.1, man/man1/html2markdown.1, man/man1/markdown2pdf.1 diff --git a/tests/Diff.hs b/tests/Diff.hs deleted file mode 100644 index f7e562ee2..000000000 --- a/tests/Diff.hs +++ /dev/null @@ -1,76 +0,0 @@ ------------------------------------------------------------------------------ --- | --- Module : Data.Algorithm.Diff --- Copyright : (c) Sterling Clover 2008 --- License : BSD 3 Clause --- Maintainer : s.clover@gmail.com --- Stability : experimental --- Portability : portable --- --- This is an implementation of the O(ND) diff algorithm as described in --- \"An O(ND) Difference Algorithm and Its Variations (1986)\" --- . It is O(mn) in space. --- The algorithm is the same one used by standared Unix diff. --- The assumption is that users of this library will want to diff over --- interesting things or peform interesting tasks with the results --- (given that, otherwise, they would simply use the standard Unix diff --- utility). Thus no attempt is made to present a fancier API to aid --- in doing standard and uninteresting things with the results. ------------------------------------------------------------------------------ - -module Diff (DI(..), getDiff, getGroupedDiff) where -import Data.Array -import Data.List - --- | Difference Indicator. A value is either from the First list, the Second --- or from Both. -data DI = F | S | B deriving (Show, Eq) - -data DL = DL {poi::Int, poj::Int, path::[DI]} deriving (Show, Eq) - -instance Ord DL where x <= y = poi x <= poi y - -canDiag :: (Eq a) => [a] -> [a] -> Int -> Int -> (Int, Int) -> Bool -canDiag as bs lena lenb = \(i,j) -> - if i < lena && j < lenb then arAs ! i == arBs ! j else False - where arAs = listArray (0,lena - 1) as - arBs = listArray (0,lenb - 1) bs - -chunk :: Int -> [a] -> [[a]] -chunk x = unfoldr (\a -> case splitAt x a of ([],[]) -> Nothing; a' -> Just a') - -dstep :: ((Int,Int)->Bool) -> [DL] -> [DL] -dstep cd dls = map maximum $ [hd]:(chunk 2 rst) - where (hd:rst) = concatMap extend dls - extend dl = let pdl = path dl - in [addsnake cd $ dl {poi=poi dl + 1, path=(F : pdl)}, - addsnake cd $ dl {poj=poj dl + 1, path=(S : pdl)}] - -addsnake :: ((Int,Int)->Bool) -> DL -> DL -addsnake cd dl - | cd (pi, pj) = addsnake cd $ - dl {poi = pi + 1, poj = pj + 1, path=(B : path dl)} - | otherwise = dl - where pi = poi dl; pj = poj dl - -lcs :: (Eq a) => [a] -> [a] -> [DI] -lcs as bs = path . head . dropWhile (\dl -> poi dl /= lena || poj dl /= lenb) . - concat . iterate (dstep cd) . (:[]) . addsnake cd $ - DL {poi=0,poj=0,path=[]} - where cd = canDiag as bs lena lenb - lena = length as; lenb = length bs - --- | Takes two lists and returns a list indicating the differences --- between them. -getDiff :: (Eq t) => [t] -> [t] -> [(DI, t)] -getDiff a b = markup a b . reverse $ lcs a b - where markup (x:xs) ys (F:ds) = (F, x) : markup xs ys ds - markup xs (y:ys) (S:ds) = (S, y) : markup xs ys ds - markup (x:xs) (_:ys) (B:ds) = (B, x) : markup xs ys ds - markup _ _ _ = [] - --- | Takes two lists and returns a list indicating the differences --- between them, grouped into chunks. -getGroupedDiff :: (Eq t) => [t] -> [t] -> [(DI, [t])] -getGroupedDiff a b = map go . groupBy (\x y -> fst x == fst y) $ getDiff a b - where go ((d,x) : xs) = (d, x : map snd xs) diff --git a/tests/RunTests.hs b/tests/RunTests.hs index 90e2276b2..f6c39b5bc 100644 --- a/tests/RunTests.hs +++ b/tests/RunTests.hs @@ -8,11 +8,14 @@ -- If the lhs argument is provided, tests for lhs support will be -- run. These presuppose that pandoc has been compiled with the -- -fhighlighting flag, so these tests are not run by default. +-- +-- This program assumes that the Diff package has been installed: +-- cabal install Diff module Main where import System.Exit import System.IO.UTF8 -import System.IO ( openTempFile, stderr ) +import System.IO ( openTempFile, stderr, stdout, hFlush ) import Prelude hiding ( putStrLn, putStr, readFile ) import System.Process ( runProcess, waitForProcess ) import System.FilePath ( (), (<.>) ) @@ -20,7 +23,7 @@ import System.Directory import System.Environment import System.Exit import Text.Printf -import Diff +import Data.Algorithm.Diff pandocPath :: FilePath pandocPath = ".." "dist" "build" "pandoc" "pandoc" @@ -143,11 +146,14 @@ runTest :: String -- ^ Title of test -> FilePath -- ^ Norm (for test results) filepath -> IO Bool runTest testname opts inp norm = do + putStr $ printf "%-28s ---> " testname (outputPath, hOut) <- openTempFile "" "pandoc-test" let inpPath = inp let normPath = norm + hFlush stdout + env <- getEnvironment -- we need at least HOME so pandoc can find data files -- Note: COLUMNS must be set for markdown table reader - ph <- runProcess pandocPath (opts ++ [inpPath]) Nothing (Just [("COLUMNS", "80")]) Nothing (Just hOut) (Just stderr) + ph <- runProcess pandocPath (opts ++ [inpPath]) Nothing (Just (("COLUMNS", "80"):env)) Nothing (Just hOut) (Just stderr) ec <- waitForProcess ph result <- if ec == ExitSuccess then do @@ -159,5 +165,5 @@ runTest testname opts inp norm = do else return $ TestFailed $ getDiff (lines outputContents) (lines normContents) else return $ TestError ec removeFile outputPath - putStrLn $ printf "%-28s ---> %s" testname (show result) + putStrLn (show result) return (result == TestPassed) -- cgit v1.2.3