From 87aaa7e719926332f69f06a4d284fc70c41fa1a8 Mon Sep 17 00:00:00 2001
From: John MacFarlane <jgm@berkeley.edu>
Date: Sat, 22 Jan 2011 14:58:32 -0800
Subject: [PATCH] Use ANSI color to point to diffs in test output.

ConTeXt writer bullet list test set to break as an example.
---
 pandoc.cabal                   |  3 ++-
 tests/Tests/Helpers.hs         | 26 ++++++++++++++++++++------
 tests/Tests/Writers/ConTeXt.hs |  4 ++--
 3 files changed, 24 insertions(+), 9 deletions(-)

diff --git a/pandoc.cabal b/pandoc.cabal
index dda8524c7..b505af1e0 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -344,7 +344,8 @@ Executable test-pandoc
                       test-framework-quickcheck2 >= 0.2.9 && < 0.3,
                       QuickCheck == 2.4.*,
                       HUnit >= 1.2 && < 1.3,
-                      template-haskell == 2.4.*
+                      template-haskell == 2.4.*,
+                      ansi-terminal == 0.5.*
     Other-Modules:    Tests.Old
                       Tests.Helpers
                       Tests.Arbitrary
diff --git a/tests/Tests/Helpers.hs b/tests/Tests/Helpers.hs
index ed67cd1e4..53bad097e 100644
--- a/tests/Tests/Helpers.hs
+++ b/tests/Tests/Helpers.hs
@@ -23,6 +23,8 @@ import Text.Pandoc.Writers.Native (writeNative)
 import Language.Haskell.TH.Quote
 import Language.Haskell.TH.Syntax (Q, runIO)
 import qualified Test.QuickCheck.Property as QP
+import System.Console.ANSI
+import Data.Algorithm.Diff
 
 lit :: QuasiQuoter
 lit = QuasiQuoter ((\a -> let b = rnl a in [|b|]) . filter (/= '\r')) $
@@ -49,20 +51,32 @@ test :: (ToString a, ToString b, ToString c)
      -> Test
 test fn name (input, expected) =
   testCase name $ assertBool msg (actual' == expected')
-     where msg = dashes "input" ++ input' ++
-                 dashes "expected" ++ expected' ++
-                 dashes "got" ++ actual' ++
+     where msg = nl ++ dashes "input" ++ nl ++ input' ++ nl ++
+                 dashes "expected" ++ nl ++ expected'' ++
+                 dashes "got" ++ nl ++ actual'' ++
                  dashes ""
+           nl = "\n"
            input'  = toString input
            actual' = toString $ fn input
            expected' = toString expected
-           dashes "" = '\n' : replicate 72 '-'
-           dashes x  = '\n' : replicate (72 - length x - 5) '-' ++ " " ++
-                              x ++ " ---\n"
+           diff = getDiff (lines expected') (lines actual')
+           expected'' = unlines $ map vividize $ filter (\(d,_) -> d /= S) diff
+           actual''   = unlines $ map vividize $ filter (\(d,_) -> d /= F) diff
+           dashes "" = replicate 72 '-'
+           dashes x  = replicate (72 - length x - 5) '-' ++ " " ++ x ++ " ---"
+
+vividize :: (DI,String) -> String
+vividize (B,s) = s
+vividize (_,s) = vivid s
 
 property :: QP.Testable a => TestName -> a -> Test
 property = testProperty
 
+vivid :: String -> String
+vivid s = setSGRCode [SetColor Background Dull Red
+                     , SetColor Foreground Vivid White] ++ s
+          ++ setSGRCode [Reset]
+
 infix 6 =?>
 (=?>) :: a -> b -> (a,b)
 x =?> y = (x, y)
diff --git a/tests/Tests/Writers/ConTeXt.hs b/tests/Tests/Writers/ConTeXt.hs
index 6f380713c..db01e1560 100644
--- a/tests/Tests/Writers/ConTeXt.hs
+++ b/tests/Tests/Writers/ConTeXt.hs
@@ -62,8 +62,8 @@ tests = [ testGroup "inline code"
     next
   \item
     \startitemize
-    \item
-      bot
+      \item
+       bot
     \stopitemize
   \stopitemize
 \stopitemize|]