diff options
author | John MacFarlane <jgm@berkeley.edu> | 2011-01-21 20:50:18 -0800 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2011-01-22 10:50:15 -0800 |
commit | 15250859c355634670ce1ad532800bca591dc99b (patch) | |
tree | 39516cc60dfc5c9562add364b5d83394e2fdbe32 /tests/Tests/Writers | |
parent | b3c1a89cdf8fe7fd919d4ccc63aeb19af3273f96 (diff) | |
download | pandoc-15250859c355634670ce1ad532800bca591dc99b.tar.gz |
Improved test framework.
Now there is a uniform interface for reader and writer tests.
Also added a quasiquoter, for multiline strings.
Diffstat (limited to 'tests/Tests/Writers')
-rw-r--r-- | tests/Tests/Writers/ConTeXt.hs | 55 |
1 files changed, 43 insertions, 12 deletions
diff --git a/tests/Tests/Writers/ConTeXt.hs b/tests/Tests/Writers/ConTeXt.hs index 1a887de1f..9b59c617d 100644 --- a/tests/Tests/Writers/ConTeXt.hs +++ b/tests/Tests/Writers/ConTeXt.hs @@ -1,29 +1,60 @@ -{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE OverloadedStrings, QuasiQuotes #-} module Tests.Writers.ConTeXt (tests) where import Test.Framework import Text.Pandoc.Builder import Text.Pandoc -import Text.Pandoc.Shared (removeTrailingSpace) import Tests.Helpers -inlines :: Inlines -> (Inlines, String) -inlines ils = (ils, removeTrailingSpace . - writeConTeXt defaultWriterOptions . doc . plain $ ils) +context :: (ToString a, ToPandoc a) => a -> String +context = writeConTeXt defaultWriterOptions . toPandoc -blocks :: Blocks -> (Blocks, String) -blocks bls = (bls, writeConTeXt defaultWriterOptions . doc $ bls) +{- + "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 '}'" =: - inlines (code "}") --> "\\mono{\\letterclosebrace{x}}" - , "without '}'" =: - inlines (code "]") --> "\\type{]}" + [ "with '}'" =: code "}" =?> "\\mono{\\letterclosebrace{}}" + , "without '}'" =: code "]" =?> "\\type{]}" ] , testGroup "headers" [ "level 1" =: - blocks (header 1 "My header") --> "\\subject{My header}" + header 1 "My header" =?> "\\subject{My header}" + ] + , 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|] ] ] |