diff options
author | John MacFarlane <fiddlosopher@gmail.com> | 2012-06-01 10:50:22 -0700 |
---|---|---|
committer | John MacFarlane <fiddlosopher@gmail.com> | 2012-06-01 10:50:22 -0700 |
commit | e14712dabd9773a44be9a29fecb903079dac162f (patch) | |
tree | d3b5f994a94a959857e5b71b16d9ca94e4180a7e /src/Tests | |
parent | 3fd80cd835b06cfcf1e3d729c2af43b5842d3b35 (diff) | |
download | pandoc-e14712dabd9773a44be9a29fecb903079dac162f.tar.gz |
LaTeX writer: Ensure newline after Verbatim at end of footnote.
This fixes a regression. Also added a test for this.
Diffstat (limited to 'src/Tests')
-rw-r--r-- | src/Tests/Writers/LaTeX.hs | 35 |
1 files changed, 35 insertions, 0 deletions
diff --git a/src/Tests/Writers/LaTeX.hs b/src/Tests/Writers/LaTeX.hs new file mode 100644 index 000000000..7987716f3 --- /dev/null +++ b/src/Tests/Writers/LaTeX.hs @@ -0,0 +1,35 @@ +{-# LANGUAGE OverloadedStrings, QuasiQuotes #-} +module Tests.Writers.LaTeX (tests) where + +import Test.Framework +import Text.Pandoc.Builder +import Text.Pandoc +import Tests.Helpers +import Tests.Arbitrary() + +latex :: (ToString a, ToPandoc a) => a -> String +latex = writeLaTeX defaultWriterOptions . toPandoc + +{- + "my test" =: X =?> Y + +is shorthand for + + test latex "my test" $ X =?> Y + +which is in turn shorthand for + + test latex "my test" (X,Y) +-} + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> Test +(=:) = test latex + +tests :: [Test] +tests = [ testGroup "code blocks" + [ "in footnotes" =: note (para "hi" <> codeBlock "hi") =?> + "\\footnote{hi\n\n\\begin{Verbatim}\nhi\n\\end{Verbatim}\n}" + ] + ] |