2013-01-23 08:47:43 -08:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2012-06-01 10:50:22 -07:00
|
|
|
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
|
2014-06-20 10:24:30 -07:00
|
|
|
latex = writeLaTeX def{ writerHighlight = True } . toPandoc
|
2012-06-01 10:50:22 -07:00
|
|
|
|
2013-08-22 20:15:36 +02:00
|
|
|
latexListing :: (ToString a, ToPandoc a) => a -> String
|
|
|
|
latexListing = writeLaTeX def{ writerListings = True } . toPandoc
|
|
|
|
|
2012-06-01 10:50:22 -07:00
|
|
|
{-
|
|
|
|
"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}"
|
2013-08-22 20:15:36 +02:00
|
|
|
, test latexListing "identifier" $ codeBlockWith ("id",[],[]) "hi" =?>
|
|
|
|
("\\begin{lstlisting}[label=id]\nhi\n\\end{lstlisting}" :: String)
|
|
|
|
, test latexListing "no identifier" $ codeBlock "hi" =?>
|
|
|
|
("\\begin{lstlisting}\nhi\n\\end{lstlisting}" :: String)
|
2012-06-01 10:50:22 -07:00
|
|
|
]
|
2013-10-21 17:33:42 -07:00
|
|
|
, testGroup "definition lists"
|
|
|
|
[ "with internal link" =: definitionList [(link "#go" "" (str "testing"),
|
|
|
|
[plain (text "hi there")])] =?>
|
2015-10-27 14:08:35 -07:00
|
|
|
"\\begin{description}\n\\tightlist\n\\item[\\hyperlink{go}{testing}]\nhi there\n\\end{description}"
|
2013-10-21 17:33:42 -07:00
|
|
|
]
|
2013-01-12 10:21:19 -08:00
|
|
|
, testGroup "math"
|
|
|
|
[ "escape |" =: para (math "\\sigma|_{\\{x\\}}") =?>
|
2014-07-29 20:45:49 -07:00
|
|
|
"\\(\\sigma|_{\\{x\\}}\\)"
|
2013-01-12 10:21:19 -08:00
|
|
|
]
|
2013-08-16 13:02:55 -07:00
|
|
|
, testGroup "headers"
|
|
|
|
[ "unnumbered header" =:
|
|
|
|
headerWith ("foo",["unnumbered"],[]) 1
|
|
|
|
(text "Header 1" <> note (plain $ text "note")) =?>
|
2014-02-13 00:03:54 +01:00
|
|
|
"\\section*{\\texorpdfstring{Header 1\\footnote{note}}{Header 1}}\\label{foo}\n\\addcontentsline{toc}{section}{Header 1}\n"
|
2014-08-31 16:04:43 -04:00
|
|
|
, "in list item" =:
|
|
|
|
bulletList [header 2 (text "foo")] =?>
|
|
|
|
"\\begin{itemize}\n\\item ~\n \\subsection{foo}\n\\end{itemize}"
|
|
|
|
, "in definition list item" =:
|
|
|
|
definitionList [(text "foo", [header 2 (text "bar"),
|
|
|
|
para $ text "baz"])] =?>
|
|
|
|
"\\begin{description}\n\\item[foo] ~ \n\\subsection{bar}\n\nbaz\n\\end{description}"
|
2014-09-09 11:05:47 -04:00
|
|
|
, "containing image" =:
|
|
|
|
header 1 (image "imgs/foo.jpg" "" (text "Alt text")) =?>
|
2014-12-15 10:03:19 -08:00
|
|
|
"\\section{\\texorpdfstring{\\protect\\includegraphics{imgs/foo.jpg}}{Alt text}}"
|
2013-08-16 13:02:55 -07:00
|
|
|
]
|
2014-06-20 10:24:30 -07:00
|
|
|
, testGroup "inline code"
|
|
|
|
[ "struck out and highlighted" =:
|
|
|
|
strikeout (codeWith ("",["haskell"],[]) "foo" <> space
|
|
|
|
<> str "bar") =?>
|
|
|
|
"\\sout{\\mbox{\\VERB|\\NormalTok{foo}|} bar}"
|
|
|
|
, "struck out and not highlighted" =:
|
|
|
|
strikeout (code "foo" <> space
|
|
|
|
<> str "bar") =?>
|
|
|
|
"\\sout{\\texttt{foo} bar}"
|
2014-06-23 12:51:10 -07:00
|
|
|
, "single quotes" =:
|
|
|
|
code "dog's" =?> "\\texttt{dog\\textquotesingle{}s}"
|
2014-06-20 10:24:30 -07:00
|
|
|
]
|
2012-06-01 10:50:22 -07:00
|
|
|
]
|