From 570d8ff08c7007c4fffd345c9bf2057201a0bdd4 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 29 Jan 2011 11:24:16 -0800 Subject: Moved tests to src. --- src/Tests/Writers/ConTeXt.hs | 72 ++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 72 insertions(+) create mode 100644 src/Tests/Writers/ConTeXt.hs (limited to 'src/Tests/Writers/ConTeXt.hs') diff --git a/src/Tests/Writers/ConTeXt.hs b/src/Tests/Writers/ConTeXt.hs new file mode 100644 index 000000000..704571e95 --- /dev/null +++ b/src/Tests/Writers/ConTeXt.hs @@ -0,0 +1,72 @@ +{-# LANGUAGE OverloadedStrings, QuasiQuotes #-} +module Tests.Writers.ConTeXt (tests) where + +import Test.Framework +import Text.Pandoc.Builder +import Text.Pandoc +import Tests.Helpers +import Tests.Arbitrary() + +context :: (ToString a, ToPandoc a) => a -> String +context = writeConTeXt defaultWriterOptions . toPandoc + +context' :: (ToString a, ToPandoc a) => a -> String +context' = writeConTeXt defaultWriterOptions{ writerWrapText = False } + . toPandoc + +{- + "my test" =: X =?> Y + +is shorthand for + + test context "my test" $ X =?> Y + +which is in turn shorthand for + + test context "my test" (X,Y) +-} + +infix 5 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> Test +(=:) = test context + +tests :: [Test] +tests = [ testGroup "inline code" + [ "with '}'" =: code "}" =?> "\\mono{\\letterclosebrace{}}" + , "without '}'" =: code "]" =?> "\\type{]}" + , property "code property" $ \s -> null s || + if '{' `elem` s || '}' `elem` s + then (context' $ code s) == "\\mono{" ++ + (context' $ str s) ++ "}" + else (context' $ code s) == "\\type{" ++ s ++ "}" + ] + , testGroup "headers" + [ "level 1" =: + header 1 "My header" =?> "\\subject{My header}" + , property "header 1 property" $ \ils -> + context' (header 1 ils) == "\\subject{" ++ context' ils ++ "}" + ] + , testGroup "bullet lists" + [ "nested" =: + bulletList [plain (text "top") + ,bulletList [plain (text "next") + ,bulletList [plain (text "bot")]]] + =?> [_LIT| +\startitemize +\item + top +\item + \startitemize + \item + next + \item + \startitemize + \item + bot + \stopitemize + \stopitemize +\stopitemize|] + ] + ] + -- cgit v1.2.3