summaryrefslogtreecommitdiff
path: root/src/Tests
diff options
context:
space:
mode:
Diffstat (limited to 'src/Tests')
-rw-r--r--src/Tests/Arbitrary.hs10
-rw-r--r--src/Tests/Helpers.hs12
-rw-r--r--src/Tests/Old.hs8
-rw-r--r--src/Tests/Readers/LaTeX.hs80
-rw-r--r--src/Tests/Readers/Markdown.hs43
-rw-r--r--src/Tests/Readers/RST.hs14
-rw-r--r--src/Tests/Writers/ConTeXt.hs6
-rw-r--r--src/Tests/Writers/HTML.hs4
-rw-r--r--src/Tests/Writers/Markdown.hs4
9 files changed, 98 insertions, 83 deletions
diff --git a/src/Tests/Arbitrary.hs b/src/Tests/Arbitrary.hs
index f5a44ceab..9d65e1f1f 100644
--- a/src/Tests/Arbitrary.hs
+++ b/src/Tests/Arbitrary.hs
@@ -1,5 +1,5 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}
-{-# LANGUAGE TypeSynonymInstances #-}
+{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, ScopedTypeVariables #-}
-- provides Arbitrary instance for Pandoc types
module Tests.Arbitrary ()
where
@@ -22,10 +22,10 @@ arbAttr = do
return (id',classes,keyvals)
instance Arbitrary Inlines where
- arbitrary = liftM fromList arbitrary
+ arbitrary = liftM (fromList :: [Inline] -> Inlines) arbitrary
instance Arbitrary Blocks where
- arbitrary = liftM fromList arbitrary
+ arbitrary = liftM (fromList :: [Block] -> Blocks) arbitrary
instance Arbitrary Inline where
arbitrary = resize 3 $ arbInline 2
@@ -41,10 +41,6 @@ arbInline :: Int -> Gen Inline
arbInline n = frequency $ [ (60, liftM Str realString)
, (60, return Space)
, (10, liftM2 Code arbAttr realString)
- , (5, return EmDash)
- , (5, return EnDash)
- , (5, return Apostrophe)
- , (5, return Ellipses)
, (5, elements [ RawInline "html" "<a id=\"eek\">"
, RawInline "latex" "\\my{command}" ])
] ++ [ x | x <- nesters, n > 1]
diff --git a/src/Tests/Helpers.hs b/src/Tests/Helpers.hs
index b8d6b83a7..66879efed 100644
--- a/src/Tests/Helpers.hs
+++ b/src/Tests/Helpers.hs
@@ -69,17 +69,15 @@ test fn name (input, expected) =
vividize :: (DI,String) -> String
vividize (B,s) = s
-vividize (_,s) = vivid s
+vividize (F,s) = s
+vividize (S,s) = setSGRCode [SetColor Background Dull Red
+ , SetColor Foreground Vivid White] ++ s
+ ++ setSGRCode [Reset]
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 =?>
+infix 5 =?>
(=?>) :: a -> b -> (a,b)
x =?> y = (x, y)
diff --git a/src/Tests/Old.hs b/src/Tests/Old.hs
index cb1417ffa..1ec32a30d 100644
--- a/src/Tests/Old.hs
+++ b/src/Tests/Old.hs
@@ -13,7 +13,6 @@ import Data.Algorithm.Diff
import Text.Pandoc.Shared ( normalize, defaultWriterOptions )
import Text.Pandoc.Writers.Native ( writeNative )
import Text.Pandoc.Readers.Native ( readNative )
-import Text.Pandoc.Highlighting ( languages )
import Prelude hiding ( readFile )
import qualified Data.ByteString.Lazy as B
import Data.ByteString.Lazy.UTF8 (toString)
@@ -105,7 +104,7 @@ tests = [ testGroup "markdown"
]
, testGroup "other writers" $ map (\f -> testGroup f $ writerTests f)
[ "docbook", "opendocument" , "context" , "texinfo"
- , "man" , "plain" , "mediawiki", "rtf", "org"
+ , "man" , "plain" , "mediawiki", "rtf", "org", "asciidoc"
]
]
@@ -121,10 +120,7 @@ lhsWriterTests format
]
where
t n f = test n ["--columns=78", "-r", "native", "-s", "-w", f]
- "lhs-test.native" ("lhs-test" <.> ext f)
- ext f = if null languages && format == "html"
- then "nohl" <.> f
- else f
+ "lhs-test.native" ("lhs-test" <.> f)
lhsReaderTest :: String -> Test
lhsReaderTest format =
diff --git a/src/Tests/Readers/LaTeX.hs b/src/Tests/Readers/LaTeX.hs
index 6d28441f8..d60026b20 100644
--- a/src/Tests/Readers/LaTeX.hs
+++ b/src/Tests/Readers/LaTeX.hs
@@ -11,7 +11,7 @@ import Text.Pandoc
latex :: String -> Pandoc
latex = readLaTeX defaultParserState
-infix 5 =:
+infix 4 =:
(=:) :: ToString c
=> String -> (String, c) -> Test
(=:) = test latex
@@ -35,10 +35,15 @@ tests = [ testGroup "basic"
"\\subsubsection{header}" =?> header 3 "header"
, "emph" =:
"\\section{text \\emph{emph}}" =?>
- header 1 ("text" +++ space +++ emph "emph")
+ header 1 ("text" <> space <> emph "emph")
, "link" =:
"\\section{text \\href{/url}{link}}" =?>
- header 1 ("text" +++ space +++ link "/url" "" "link")
+ header 1 ("text" <> space <> link "/url" "" "link")
+ ]
+
+ , testGroup "math"
+ [ "escaped $" =:
+ "$x=\\$4$" =?> para (math "x=\\$4")
]
, testGroup "space and comments"
@@ -64,98 +69,101 @@ baseCitation = Citation{ citationId = "item1"
, citationNoteNum = 0
, citationHash = 0 }
+rt :: String -> Inlines
+rt = rawInline "latex"
+
natbibCitations :: Test
natbibCitations = testGroup "natbib"
[ "citet" =: "\\citet{item1}"
- =?> para (cite [baseCitation] empty)
+ =?> para (cite [baseCitation] (rt "\\citet{item1}"))
, "suffix" =: "\\citet[p.~30]{item1}"
=?> para
- (cite [baseCitation{ citationSuffix = toList $ text "p.\160\&30" }] empty)
+ (cite [baseCitation{ citationSuffix = toList $ text ", p.\160\&30" }] (rt "\\citet[p.~30]{item1}"))
, "suffix long" =: "\\citet[p.~30, with suffix]{item1}"
=?> para (cite [baseCitation{ citationSuffix =
- toList $ text "p.\160\&30, with suffix" }] empty)
+ toList $ text ", p.\160\&30, with suffix" }] (rt "\\citet[p.~30, with suffix]{item1}"))
, "multiple" =: "\\citeauthor{item1} \\citetext{\\citeyear{item1}; \\citeyear[p.~30]{item2}; \\citealp[see also][]{item3}}"
=?> para (cite [baseCitation{ citationMode = AuthorInText }
,baseCitation{ citationMode = SuppressAuthor
- , citationSuffix = [Str "p.\160\&30"]
+ , citationSuffix = [Str ",",Space,Str "p.\160\&30"]
, citationId = "item2" }
,baseCitation{ citationId = "item3"
, citationPrefix = [Str "see",Space,Str "also"]
, citationMode = NormalCitation }
- ] empty)
+ ] (rt "\\citetext{\\citeyear{item1}; \\citeyear[p.~30]{item2}; \\citealp[see also][]{item3}}"))
, "group" =: "\\citetext{\\citealp[see][p.~34--35]{item1}; \\citealp[also][chap. 3]{item3}}"
=?> para (cite [baseCitation{ citationMode = NormalCitation
, citationPrefix = [Str "see"]
- , citationSuffix = [Str "p.\160\&34",EnDash,Str "35"] }
+ , citationSuffix = [Str ",",Space,Str "p.\160\&34\8211\&35"] }
,baseCitation{ citationMode = NormalCitation
, citationId = "item3"
, citationPrefix = [Str "also"]
- , citationSuffix = [Str "chap.",Space,Str "3"] }
- ] empty)
+ , citationSuffix = [Str ",",Space,Str "chap.",Space,Str "3"] }
+ ] (rt "\\citetext{\\citealp[see][p.~34--35]{item1}; \\citealp[also][chap. 3]{item3}}"))
, "suffix and locator" =: "\\citep[pp.~33, 35--37, and nowhere else]{item1}"
=?> para (cite [baseCitation{ citationMode = NormalCitation
- , citationSuffix = [Str "pp.\160\&33,",Space,Str "35",EnDash,Str "37,",Space,Str "and",Space,Str "nowhere",Space, Str "else"] }] empty)
+ , citationSuffix = [Str ",",Space,Str "pp.\160\&33,",Space,Str "35\8211\&37,",Space,Str "and",Space,Str "nowhere",Space, Str "else"] }] (rt "\\citep[pp.~33, 35--37, and nowhere else]{item1}"))
, "suffix only" =: "\\citep[and nowhere else]{item1}"
=?> para (cite [baseCitation{ citationMode = NormalCitation
- , citationSuffix = toList $ text "and nowhere else" }] empty)
+ , citationSuffix = toList $ text ", and nowhere else" }] (rt "\\citep[and nowhere else]{item1}"))
, "no author" =: "\\citeyearpar{item1}, and now Doe with a locator \\citeyearpar[p.~44]{item2}"
- =?> para (cite [baseCitation{ citationMode = SuppressAuthor }] empty +++
- text ", and now Doe with a locator " +++
+ =?> para (cite [baseCitation{ citationMode = SuppressAuthor }] (rt "\\citeyearpar{item1}") <>
+ text ", and now Doe with a locator " <>
cite [baseCitation{ citationMode = SuppressAuthor
- , citationSuffix = [Str "p.\160\&44"]
- , citationId = "item2" }] empty)
+ , citationSuffix = [Str ",",Space,Str "p.\160\&44"]
+ , citationId = "item2" }] (rt "\\citeyearpar[p.~44]{item2}"))
, "markup" =: "\\citep[\\emph{see}][p. \\textbf{32}]{item1}"
=?> para (cite [baseCitation{ citationMode = NormalCitation
, citationPrefix = [Emph [Str "see"]]
- , citationSuffix = [Str "p.",Space,
- Strong [Str "32"]] }] empty)
+ , citationSuffix = [Str ",",Space,Str "p.",Space,
+ Strong [Str "32"]] }] (rt "\\citep[\\emph{see}][p. \\textbf{32}]{item1}"))
]
biblatexCitations :: Test
biblatexCitations = testGroup "biblatex"
[ "textcite" =: "\\textcite{item1}"
- =?> para (cite [baseCitation] empty)
+ =?> para (cite [baseCitation] (rt "\\textcite{item1}"))
, "suffix" =: "\\textcite[p.~30]{item1}"
=?> para
- (cite [baseCitation{ citationSuffix = toList $ text "p.\160\&30" }] empty)
+ (cite [baseCitation{ citationSuffix = toList $ text ", p.\160\&30" }] (rt "\\textcite[p.~30]{item1}"))
, "suffix long" =: "\\textcite[p.~30, with suffix]{item1}"
=?> para (cite [baseCitation{ citationSuffix =
- toList $ text "p.\160\&30, with suffix" }] empty)
+ toList $ text ", p.\160\&30, with suffix" }] (rt "\\textcite[p.~30, with suffix]{item1}"))
, "multiple" =: "\\textcites{item1}[p.~30]{item2}[see also][]{item3}"
=?> para (cite [baseCitation{ citationMode = AuthorInText }
,baseCitation{ citationMode = NormalCitation
- , citationSuffix = [Str "p.\160\&30"]
+ , citationSuffix = [Str ",",Space,Str "p.\160\&30"]
, citationId = "item2" }
,baseCitation{ citationId = "item3"
, citationPrefix = [Str "see",Space,Str "also"]
, citationMode = NormalCitation }
- ] empty)
+ ] (rt "\\textcites{item1}[p.~30]{item2}[see also][]{item3}"))
, "group" =: "\\autocites[see][p.~34--35]{item1}[also][chap. 3]{item3}"
=?> para (cite [baseCitation{ citationMode = NormalCitation
, citationPrefix = [Str "see"]
- , citationSuffix = [Str "p.\160\&34",EnDash,Str "35"] }
+ , citationSuffix = [Str ",",Space,Str "p.\160\&34\8211\&35"] }
,baseCitation{ citationMode = NormalCitation
, citationId = "item3"
, citationPrefix = [Str "also"]
- , citationSuffix = [Str "chap.",Space,Str "3"] }
- ] empty)
+ , citationSuffix = [Str ",",Space,Str "chap.",Space,Str "3"] }
+ ] (rt "\\autocites[see][p.~34--35]{item1}[also][chap. 3]{item3}"))
, "suffix and locator" =: "\\autocite[pp.~33, 35--37, and nowhere else]{item1}"
=?> para (cite [baseCitation{ citationMode = NormalCitation
- , citationSuffix = [Str "pp.\160\&33,",Space,Str "35",EnDash,Str "37,",Space,Str "and",Space,Str "nowhere",Space, Str "else"] }] empty)
+ , citationSuffix = [Str ",",Space,Str "pp.\160\&33,",Space,Str "35\8211\&37,",Space,Str "and",Space,Str "nowhere",Space, Str "else"] }] (rt "\\autocite[pp.~33, 35--37, and nowhere else]{item1}"))
, "suffix only" =: "\\autocite[and nowhere else]{item1}"
=?> para (cite [baseCitation{ citationMode = NormalCitation
- , citationSuffix = toList $ text "and nowhere else" }] empty)
+ , citationSuffix = toList $ text ", and nowhere else" }] (rt "\\autocite[and nowhere else]{item1}"))
, "no author" =: "\\autocite*{item1}, and now Doe with a locator \\autocite*[p.~44]{item2}"
- =?> para (cite [baseCitation{ citationMode = SuppressAuthor }] empty +++
- text ", and now Doe with a locator " +++
+ =?> para (cite [baseCitation{ citationMode = SuppressAuthor }] (rt "\\autocite*{item1}") <>
+ text ", and now Doe with a locator " <>
cite [baseCitation{ citationMode = SuppressAuthor
- , citationSuffix = [Str "p.\160\&44"]
- , citationId = "item2" }] empty)
+ , citationSuffix = [Str ",",Space,Str "p.\160\&44"]
+ , citationId = "item2" }] (rt "\\autocite*[p.~44]{item2}"))
, "markup" =: "\\autocite[\\emph{see}][p. \\textbf{32}]{item1}"
=?> para (cite [baseCitation{ citationMode = NormalCitation
, citationPrefix = [Emph [Str "see"]]
- , citationSuffix = [Str "p.",Space,
- Strong [Str "32"]] }] empty)
+ , citationSuffix = [Str ",",Space,Str "p.",Space,
+ Strong [Str "32"]] }] (rt "\\autocite[\\emph{see}][p. \\textbf{32}]{item1}"))
, "parencite" =: "\\parencite{item1}"
- =?> para (cite [baseCitation{ citationMode = NormalCitation }] empty)
+ =?> para (cite [baseCitation{ citationMode = NormalCitation }] (rt "\\parencite{item1}"))
]
diff --git a/src/Tests/Readers/Markdown.hs b/src/Tests/Readers/Markdown.hs
index 941762bd0..5ad974adf 100644
--- a/src/Tests/Readers/Markdown.hs
+++ b/src/Tests/Readers/Markdown.hs
@@ -8,7 +8,6 @@ import Tests.Arbitrary()
import Text.Pandoc.Builder
-- import Text.Pandoc.Shared ( normalize )
import Text.Pandoc
-import Data.Sequence (singleton)
markdown :: String -> Pandoc
markdown = readMarkdown defaultParserState{ stateStandalone = True }
@@ -16,7 +15,7 @@ markdown = readMarkdown defaultParserState{ stateStandalone = True }
markdownSmart :: String -> Pandoc
markdownSmart = readMarkdown defaultParserState{ stateSmart = True }
-infix 5 =:
+infix 4 =:
(=:) :: ToString c
=> String -> (String, c) -> Test
(=:) = test markdown
@@ -44,29 +43,49 @@ tests = [ testGroup "inline code"
"`*` {.haskell .special x=\"7\"}"
=?> para (codeWith ("",["haskell","special"],[("x","7")]) "*")
]
+ , testGroup "backslash escapes"
+ [ "in URL" =:
+ "[hi](/there\\))"
+ =?> para (link "/there)" "" "hi")
+ , "in title" =:
+ "[hi](/there \"a\\\"a\")"
+ =?> para (link "/there" "a\"a" "hi")
+ , "in reference link title" =:
+ "[hi]\n\n[hi]: /there (a\\)a)"
+ =?> para (link "/there" "a)a" "hi")
+ , "in reference link URL" =:
+ "[hi]\n\n[hi]: /there\\.0"
+ =?> para (link "/there.0" "" "hi")
+ ]
, testGroup "smart punctuation"
[ test markdownSmart "quote before ellipses"
("'...hi'"
- =?> para (singleQuoted (singleton Ellipses +++ "hi")))
+ =?> para (singleQuoted ("…hi")))
+ , test markdownSmart "apostrophe before emph"
+ ("D'oh! A l'*aide*!"
+ =?> para ("D’oh! A l’" <> emph "aide" <> "!"))
+ , test markdownSmart "apostrophe in French"
+ ("À l'arrivée de la guerre, le thème de l'«impossibilité du socialisme»"
+ =?> para ("À l’arrivée de la guerre, le thème de l’«impossibilité du socialisme»"))
]
, testGroup "mixed emphasis and strong"
[ "emph and strong emph alternating" =:
"*xxx* ***xxx*** xxx\n*xxx* ***xxx*** xxx"
- =?> para (emph "xxx" +++ space +++ strong (emph "xxx") +++
- space +++ "xxx" +++ space +++
- emph "xxx" +++ space +++ strong (emph "xxx") +++
- space +++ "xxx")
+ =?> para (emph "xxx" <> space <> strong (emph "xxx") <>
+ space <> "xxx" <> space <>
+ emph "xxx" <> space <> strong (emph "xxx") <>
+ space <> "xxx")
, "emph with spaced strong" =:
"*x **xx** x*"
- =?> para (emph ("x" +++ space +++ strong "xx" +++ space +++ "x"))
+ =?> para (emph ("x" <> space <> strong "xx" <> space <> "x"))
]
, testGroup "footnotes"
[ "indent followed by newline and flush-left text" =:
"[^1]\n\n[^1]: my note\n\n \nnot in note\n"
- =?> para (note (para "my note")) +++ para "not in note"
+ =?> para (note (para "my note")) <> para "not in note"
, "indent followed by newline and indented text" =:
"[^1]\n\n[^1]: my note\n \n in note\n"
- =?> para (note (para "my note" +++ para "in note"))
+ =?> para (note (para "my note" <> para "in note"))
, "recursive note" =:
"[^1]\n\n[^1]: See [^1]\n"
=?> para (note (para "See [^1]"))
@@ -76,9 +95,9 @@ tests = [ testGroup "inline code"
"inverse bird tracks and html" $
"> a\n\n< b\n\n<div>\n"
=?> codeBlockWith ("",["sourceCode","literate","haskell"],[]) "a"
- +++
+ <>
codeBlockWith ("",["sourceCode","haskell"],[]) "b"
- +++
+ <>
rawBlock "html" "<div>\n\n"
]
-- the round-trip properties frequently fail
diff --git a/src/Tests/Readers/RST.hs b/src/Tests/Readers/RST.hs
index 4b8c9301b..3269092a6 100644
--- a/src/Tests/Readers/RST.hs
+++ b/src/Tests/Readers/RST.hs
@@ -11,15 +11,15 @@ import Text.Pandoc
rst :: String -> Pandoc
rst = readRST defaultParserState{ stateStandalone = True }
-infix 5 =:
+infix 4 =:
(=:) :: ToString c
=> String -> (String, c) -> Test
(=:) = test rst
tests :: [Test]
tests = [ "line block with blank line" =:
- "| a\n|\n| b" =?> para (str "a" +++ linebreak +++
- linebreak +++ str " " +++ str "b")
+ "| a\n|\n| b" =?> para (str "a" <> linebreak <>
+ linebreak <> str " " <> str "b")
, "field list" =:
[_LIT|
:Hostname: media08
@@ -51,10 +51,10 @@ tests = [ "line block with blank line" =:
, "URLs with following punctuation" =:
("http://google.com, http://yahoo.com; http://foo.bar.baz.\n" ++
"http://foo.bar/baz_(bam) (http://foo.bar)") =?>
- para (link "http://google.com" "" "http://google.com" +++ ", " +++
- link "http://yahoo.com" "" "http://yahoo.com" +++ "; " +++
- link "http://foo.bar.baz" "" "http://foo.bar.baz" +++ ". " +++
+ para (link "http://google.com" "" "http://google.com" <> ", " <>
+ link "http://yahoo.com" "" "http://yahoo.com" <> "; " <>
+ link "http://foo.bar.baz" "" "http://foo.bar.baz" <> ". " <>
link "http://foo.bar/baz_(bam)" "" "http://foo.bar/baz_(bam)"
- +++ " (" +++ link "http://foo.bar" "" "http://foo.bar" +++ ")")
+ <> " (" <> link "http://foo.bar" "" "http://foo.bar" <> ")")
]
diff --git a/src/Tests/Writers/ConTeXt.hs b/src/Tests/Writers/ConTeXt.hs
index 704571e95..506ff698f 100644
--- a/src/Tests/Writers/ConTeXt.hs
+++ b/src/Tests/Writers/ConTeXt.hs
@@ -26,7 +26,7 @@ which is in turn shorthand for
test context "my test" (X,Y)
-}
-infix 5 =:
+infix 4 =:
(=:) :: (ToString a, ToPandoc a)
=> String -> (a, String) -> Test
(=:) = test context
@@ -43,9 +43,7 @@ tests = [ testGroup "inline code"
]
, testGroup "headers"
[ "level 1" =:
- header 1 "My header" =?> "\\subject{My header}"
- , property "header 1 property" $ \ils ->
- context' (header 1 ils) == "\\subject{" ++ context' ils ++ "}"
+ header 1 "My header" =?> "\\section[my-header]{My header}"
]
, testGroup "bullet lists"
[ "nested" =:
diff --git a/src/Tests/Writers/HTML.hs b/src/Tests/Writers/HTML.hs
index 3e1e0ddc2..8561aa421 100644
--- a/src/Tests/Writers/HTML.hs
+++ b/src/Tests/Writers/HTML.hs
@@ -23,7 +23,7 @@ which is in turn shorthand for
test html "my test" (X,Y)
-}
-infix 5 =:
+infix 4 =:
(=:) :: (ToString a, ToPandoc a)
=> String -> (a, String) -> Test
(=:) = test html
@@ -40,7 +40,7 @@ tests = [ testGroup "inline code"
]
, testGroup "images"
[ "alt with formatting" =:
- image "/url" "title" ("my " +++ emph "image")
+ image "/url" "title" ("my " <> emph "image")
=?> "<img src=\"/url\" title=\"title\" alt=\"my image\" />"
]
]
diff --git a/src/Tests/Writers/Markdown.hs b/src/Tests/Writers/Markdown.hs
index 70266a683..d90dc83b1 100644
--- a/src/Tests/Writers/Markdown.hs
+++ b/src/Tests/Writers/Markdown.hs
@@ -22,13 +22,13 @@ which is in turn shorthand for
test markdown "my test" (X,Y)
-}
-infix 5 =:
+infix 4 =:
(=:) :: (ToString a, ToPandoc a)
=> String -> (a, String) -> Test
(=:) = test markdown
tests :: [Test]
tests = [ "indented code after list"
- =: (orderedList [ para "one" +++ para "two" ] +++ codeBlock "test")
+ =: (orderedList [ para "one" <> para "two" ] <> codeBlock "test")
=?> "1. one\n\n two\n\n<!-- -->\n\n test"
]