aboutsummaryrefslogtreecommitdiff
path: root/test
diff options
context:
space:
mode:
Diffstat (limited to 'test')
-rw-r--r--test/Tests/Writers/Ms.hs37
-rw-r--r--test/docx/golden/inline_formatting.docxbin9989 -> 9987 bytes
-rw-r--r--test/docx/inline_formatting.native2
-rw-r--r--test/ipynb/simple.out.native6
-rw-r--r--test/lhs-test.latex3
-rw-r--r--test/lhs-test.latex+lhs3
-rw-r--r--test/test-pandoc.hs2
-rw-r--r--test/writer.jira4
-rw-r--r--test/writer.latex3
-rw-r--r--test/writers-lang-and-dir.latex3
10 files changed, 57 insertions, 6 deletions
diff --git a/test/Tests/Writers/Ms.hs b/test/Tests/Writers/Ms.hs
new file mode 100644
index 000000000..d73603314
--- /dev/null
+++ b/test/Tests/Writers/Ms.hs
@@ -0,0 +1,37 @@
+{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Writers.Ms (tests) where
+
+import Prelude
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Builder
+
+infix 4 =:
+(=:) :: (ToString a, ToPandoc a)
+ => String -> (a, String) -> TestTree
+(=:) = test (purely (writeMs def . toPandoc))
+
+tests :: [TestTree]
+tests = [ testGroup "code blocks"
+ [ "basic"
+ =: codeBlock "hello"
+ =?> unlines
+ [ ".IP"
+ , ".nf"
+ , "\\f[C]"
+ , "hello"
+ , "\\f[]"
+ , ".fi"]
+ , "escape starting ."
+ =: codeBlock ". hello"
+ =?> unlines
+ [ ".IP"
+ , ".nf"
+ , "\\f[C]"
+ , "\\&. hello"
+ , "\\f[]"
+ , ".fi"]
+ ]
+ ]
diff --git a/test/docx/golden/inline_formatting.docx b/test/docx/golden/inline_formatting.docx
index 5efe66edd..ddfd45280 100644
--- a/test/docx/golden/inline_formatting.docx
+++ b/test/docx/golden/inline_formatting.docx
Binary files differ
diff --git a/test/docx/inline_formatting.native b/test/docx/inline_formatting.native
index 000896df9..df749ffef 100644
--- a/test/docx/inline_formatting.native
+++ b/test/docx/inline_formatting.native
@@ -1,6 +1,6 @@
Pandoc (Meta {unMeta = fromList []})
[Para [Str "Regular",Space,Str "text",Space,Emph [Str "italics"],Space,Strong [Str "bold",Space,Emph [Str "bold",Space,Str "italics"]],Str "."]
,Para [Str "This",Space,Str "is",Space,SmallCaps [Str "Small",Space,Str "Caps"],Str ",",Space,Str "and",Space,Str "this",Space,Str "is",Space,Strikeout [Str "strikethrough"],Str "."]
-,Para [Str "Some",Space,Str "people",Space,Str "use",Space,Underline [Str "single",Space,Str "underlines",Space,Str "for",Space],Emph [Underline [Str "emphasis"]],Str "."]
+,Para [Str "Some",Space,Str "people",Space,Str "use",Space,Underline [Str "single",Space,Str "underlines",Space,Str "for",Space,Emph [Str "emphasis"]],Str "."]
,Para [Str "Above",Space,Str "the",Space,Str "line",Space,Str "is",Space,Superscript [Str "superscript"],Space,Str "and",Space,Str "below",Space,Str "the",Space,Str "line",Space,Str "is",Space,Subscript [Str "subscript"],Str "."]
,Para [Str "A",Space,Str "line",LineBreak,Str "break."]]
diff --git a/test/ipynb/simple.out.native b/test/ipynb/simple.out.native
index 960230894..4c060b82f 100644
--- a/test/ipynb/simple.out.native
+++ b/test/ipynb/simple.out.native
@@ -1,15 +1,15 @@
Pandoc (Meta {unMeta = fromList [("jupyter",MetaMap (fromList [("nbformat",MetaString "4"),("nbformat_minor",MetaString "5")]))]})
-[Div ("",["cell","markdown"],[("source","Lorem ipsum\n===========\n\n**Lorem ipsum** dolor sit amet, consectetur adipiscing elit. Nunc luctus\nbibendum felis dictum sodales.")])
+[Div ("",["cell","markdown"],[])
[Header 1 ("lorem-ipsum",[],[]) [Str "Lorem",Space,Str "ipsum"]
,Para [Strong [Str "Lorem",Space,Str "ipsum"],Space,Str "dolor",Space,Str "sit",Space,Str "amet,",Space,Str "consectetur",Space,Str "adipiscing",Space,Str "elit.",Space,Str "Nunc",Space,Str "luctus",SoftBreak,Str "bibendum",Space,Str "felis",Space,Str "dictum",Space,Str "sodales."]]
,Div ("",["cell","code"],[])
[CodeBlock ("",["python"],[]) "print(\"hello\")"]
-,Div ("",["cell","markdown"],[("source","Pyout\n-----")])
+,Div ("",["cell","markdown"],[])
[Header 2 ("pyout",[],[]) [Str "Pyout"]]
,Div ("",["cell","code"],[("execution_count","2")])
[CodeBlock ("",["python"],[]) "from IPython.display import HTML\nHTML(\"\"\"\n<script>\nconsole.log(\"hello\");\n</script>\n<b>HTML</b>\n\"\"\")"
,Div ("",["output","execute_result"],[("execution_count","2")])
[RawBlock (Format "html") "<script>\nconsole.log(\"hello\");\n</script>\n<b>HTML</b>\nhello"]]
-,Div ("",["cell","markdown"],[("source","Image\n-----\n\nThis image ![the moon](attachment:lalune.jpg) will be included as a cell\nattachment."),("tags","[\"foo\",\"bar\"]")])
+,Div ("",["cell","markdown"],[("tags","[\"foo\",\"bar\"]")])
[Header 2 ("image",[],[]) [Str "Image"]
,Para [Str "This",Space,Str "image",Space,Image ("",[],[]) [Str "the",Space,Str "moon"] ("lalune.jpg",""),Space,Str "will",Space,Str "be",Space,Str "included",Space,Str "as",Space,Str "a",Space,Str "cell",SoftBreak,Str "attachment."]]]
diff --git a/test/lhs-test.latex b/test/lhs-test.latex
index 48d557b27..5dade622f 100644
--- a/test/lhs-test.latex
+++ b/test/lhs-test.latex
@@ -81,6 +81,9 @@
\providecommand{\tightlist}{%
\setlength{\itemsep}{0pt}\setlength{\parskip}{0pt}}
\setcounter{secnumdepth}{-\maxdimen} % remove section numbering
+\ifluatex
+ \usepackage{selnolig} % disable illegal ligatures
+\fi
\author{}
\date{}
diff --git a/test/lhs-test.latex+lhs b/test/lhs-test.latex+lhs
index 806cf598d..cd229e107 100644
--- a/test/lhs-test.latex+lhs
+++ b/test/lhs-test.latex+lhs
@@ -48,6 +48,9 @@
\providecommand{\tightlist}{%
\setlength{\itemsep}{0pt}\setlength{\parskip}{0pt}}
\setcounter{secnumdepth}{-\maxdimen} % remove section numbering
+\ifluatex
+ \usepackage{selnolig} % disable illegal ligatures
+\fi
\author{}
\date{}
diff --git a/test/test-pandoc.hs b/test/test-pandoc.hs
index ff7661094..d0a1a6f18 100644
--- a/test/test-pandoc.hs
+++ b/test/test-pandoc.hs
@@ -37,6 +37,7 @@ import qualified Tests.Writers.JATS
import qualified Tests.Writers.Jira
import qualified Tests.Writers.LaTeX
import qualified Tests.Writers.Markdown
+import qualified Tests.Writers.Ms
import qualified Tests.Writers.Muse
import qualified Tests.Writers.Native
import qualified Tests.Writers.Org
@@ -70,6 +71,7 @@ tests pandocPath = testGroup "pandoc tests"
, testGroup "Muse" Tests.Writers.Muse.tests
, testGroup "FB2" Tests.Writers.FB2.tests
, testGroup "PowerPoint" Tests.Writers.Powerpoint.tests
+ , testGroup "Ms" Tests.Writers.Ms.tests
]
, testGroup "Readers"
[ testGroup "LaTeX" Tests.Readers.LaTeX.tests
diff --git a/test/writer.jira b/test/writer.jira
index 14080c230..aff0dc320 100644
--- a/test/writer.jira
+++ b/test/writer.jira
@@ -513,9 +513,9 @@ or here: <http://example.com/>
h1. {anchor:images}Images
From "Voyage dans la Lune" by Georges Melies \(1902):
-!lalune.jpg|title=fig:Voyage dans la Lune!
+!lalune.jpg|title=fig:Voyage dans la Lune, alt=lalune!
-Here is a movie !movie.jpg! icon.
+Here is a movie !movie.jpg|alt=movie! icon.
----
h1. {anchor:footnotes}Footnotes
diff --git a/test/writer.latex b/test/writer.latex
index e859e2d2e..05dccbb1f 100644
--- a/test/writer.latex
+++ b/test/writer.latex
@@ -63,6 +63,9 @@
\providecommand{\tightlist}{%
\setlength{\itemsep}{0pt}\setlength{\parskip}{0pt}}
\setcounter{secnumdepth}{-\maxdimen} % remove section numbering
+\ifluatex
+ \usepackage{selnolig} % disable illegal ligatures
+\fi
\title{Pandoc Test Suite}
\author{John MacFarlane \and Anonymous}
diff --git a/test/writers-lang-and-dir.latex b/test/writers-lang-and-dir.latex
index a9eefb32f..2e29bb196 100644
--- a/test/writers-lang-and-dir.latex
+++ b/test/writers-lang-and-dir.latex
@@ -66,6 +66,9 @@
\newcommand{\textfrench}[2][]{\foreignlanguage{french}{#2}}
\newenvironment{french}[2][]{\begin{otherlanguage}{french}}{\end{otherlanguage}}
\fi
+\ifluatex
+ \usepackage{selnolig} % disable illegal ligatures
+\fi
\ifxetex
% Load bidi as late as possible as it modifies e.g. graphicx
\usepackage{bidi}