" $ "
hello
" =?> + doc (divWith ("", [], [("role", "main")]) (plain (text "hello"))) + , test htmlNativeDivs "
becomes
" $ "
hello
" =?> + doc (divWith ("", [], [("role", "foobar")]) (plain (text "hello"))) + , test htmlNativeDivs "
has attributes preserved" $ "
hello
" =?> + doc (divWith ("foo", ["bar"], [("role", "main"), ("data-baz", "qux")]) (plain (text "hello"))) + , test htmlNativeDivs "
closes

" $ "

hello

main content
" =?> + doc (para (text "hello") <> divWith ("", [], [("role", "main")]) (plain (text "main content"))) + , test htmlNativeDivs "
followed by text" $ "
main content
non-main content" =?> + doc (divWith ("", [], [("role", "main")]) (plain (text "main content")) <> plain (text "non-main content")) + ] + ] diff --git a/test/Tests/Readers/JATS.hs.orig b/test/Tests/Readers/JATS.hs.orig new file mode 100644 index 000000000..5c7dfa77c --- /dev/null +++ b/test/Tests/Readers/JATS.hs.orig @@ -0,0 +1,116 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Readers.JATS (tests) where + +import Data.Text (Text) +import Test.Tasty +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder + +jats :: Text -> Pandoc +jats = purely $ readJATS def + +tests :: [TestTree] +tests = [ testGroup "inline code" + [ test jats "basic" $ "

\n @&\n

" =?> para (code "@&") + , test jats "lang" $ "

\n @&\n

" =?> para (codeWith ("", ["c"], []) "@&") + ] + , testGroup "block code" + [ test jats "basic" $ "@&" =?> codeBlock "@&" + , test jats "lang" $ "@&" =?> codeBlockWith ("", ["c"], []) "@&" + ] + , testGroup "images" + [ test jats "basic" $ "" + =?> para (image "/url" "title" mempty) + ] + , test jats "bullet list" $ + "\n\ + \ \n\ + \

\n\ + \ first\n\ + \

\n\ + \
\n\ + \ \n\ + \

\n\ + \ second\n\ + \

\n\ + \
\n\ + \ \n\ + \

\n\ + \ third\n\ + \

\n\ + \
\n\ + \
" + =?> bulletList [ para $ text "first" + , para $ text "second" + , para $ text "third" + ] + , testGroup "definition lists" + [ test jats "with internal link" $ + "\n\ + \ \n\ + \ \n\ + \ testing\n\ + \ \n\ + \ \n\ + \

\n\ + \ hi there\n\ + \

\n\ + \
\n\ + \
\n\ + \
" + =?> definitionList [(link "#go" "" (str "testing"), + [para (text "hi there")])] + ] + , testGroup "math" + [ test jats "escape |" $ + "

\n\ + \ \n\ + \ \n\ + \ σ|{x}\n\ + \

" + =?> para (math "\\sigma|_{\\{x\\}}") + , test jats "tex-math only" $ + "

\n\ + \ \n\ + \ \n\ + \

" + =?> para (math "\\sigma|_{\\{x\\}}") + , test jats "math ml only" $ + "

\n\ + \ \n\ + \ σ|{x}\n\ + \

" + =?> para (math "\\sigma|_{\\{ x\\}}") + ] + , testGroup "headers" +-- TODO fix footnotes in headers +-- [ test jats "unnumbered header" $ +-- "\n\ +-- \ Header 1<fn>\n\ +-- \ <p>\n\ +-- \ note\n\ +-- \ </p>\n\ +-- \ </fn>\n\ +-- \" +-- =?> header 1 +-- (text "Header 1" <> note (plain $ text "note")) + [ test jats "unnumbered sub header" $ + "\n\ + \ Header\n\ + \ \n\ + \ Sub-Header\n\ + \ \n\ + \" + =?> headerWith ("foo", [], []) 1 + (text "Header") + <> headerWith ("foo2", [], []) 2 + (text "Sub-Header") + , test jats "containing image" $ + "\n\ + \ <inline-graphic mimetype=\"image\" mime-subtype=\"jpeg\" xlink:href=\"imgs/foo.jpg\" />\n\ + \" + =?> header 1 (image "imgs/foo.jpg" "" mempty) + ] + ] diff --git a/test/Tests/Readers/LaTeX.hs.orig b/test/Tests/Readers/LaTeX.hs.orig new file mode 100644 index 000000000..4396d550f --- /dev/null +++ b/test/Tests/Readers/LaTeX.hs.orig @@ -0,0 +1,341 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Readers.LaTeX (tests) where + +import Data.Text (Text) +import qualified Data.Text as T +import qualified Text.Pandoc.UTF8 as UTF8 +import Text.Pandoc.Readers.LaTeX (tokenize, untokenize) +import Test.Tasty +import Test.Tasty.HUnit +import Test.Tasty.QuickCheck +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder + +latex :: Text -> Pandoc +latex = purely $ readLaTeX def{ + readerExtensions = getDefaultExtensions "latex" } + +infix 4 =: +(=:) :: ToString c + => String -> (Text, c) -> TestTree +(=:) = test latex + +simpleTable' :: [Alignment] -> [[Blocks]] -> Blocks +simpleTable' aligns = table "" (zip aligns (repeat 0.0)) + (map (const mempty) aligns) + +tokUntokRt :: String -> Bool +tokUntokRt s = untokenize (tokenize "random" t) == t + where t = T.pack s + +tests :: [TestTree] +tests = [ testGroup "tokenization" + [ testCase "tokenizer round trip on test case" $ do + orig <- T.pack <$> UTF8.readFile "../test/latex-reader.latex" + let new = untokenize $ tokenize "../test/latex-reader.latex" + orig + assertEqual "untokenize . tokenize is identity" orig new + , testProperty "untokenize . tokenize is identity" tokUntokRt + ] + + , testGroup "basic" + [ "simple" =: + "word" =?> para "word" + , "space" =: + "some text" =?> para "some text" + , "emphasized" =: + "\\emph{emphasized}" =?> para (emph "emphasized") + ] + + , testGroup "headers" + [ "level 1" =: + "\\section{header}" =?> headerWith ("header",[],[]) 1 "header" + , "level 2" =: + "\\subsection{header}" =?> headerWith ("header",[],[]) 2 "header" + , "level 3" =: + "\\subsubsection{header}" =?> headerWith ("header",[],[]) 3 "header" + , "emph" =: + "\\section{text \\emph{emph}}" =?> + headerWith ("text-emph",[],[]) 1 ("text" <> space <> emph "emph") + , "link" =: + "\\section{text \\href{/url}{link}}" =?> + headerWith ("text-link",[],[]) 1 ("text" <> space <> link "/url" "" "link") + ] + + , testGroup "math" + [ "escaped $" =: + "$x=\\$4$" =?> para (math "x=\\$4") + ] + + , testGroup "space and comments" + [ "blank lines + space at beginning" =: + "\n \n hi" =?> para "hi" + , "blank lines + space + comments" =: + "% my comment\n\n \n % another\n\nhi" =?> para "hi" + , "comment in paragraph" =: + "hi % this is a comment\nthere\n" =?> + para ("hi" <> softbreak <> "there") + ] + + , testGroup "code blocks" + [ "identifier" =: + "\\begin{lstlisting}[label=test]\\end{lstlisting}" =?> codeBlockWith ("test", [], [("label","test")]) "" + , "no identifier" =: + "\\begin{lstlisting}\\end{lstlisting}" =?> codeBlock "" + ] + + , testGroup "tables" + [ "Single cell table" =: + "\\begin{tabular}{|l|}Test\\\\\\end{tabular}" =?> + simpleTable' [AlignLeft] [[plain "Test"]] + , "Multi cell table" =: + "\\begin{tabular}{|rl|}One & Two\\\\ \\end{tabular}" =?> + simpleTable' [AlignRight,AlignLeft] [[plain "One", plain "Two"]] + , "Multi line table" =: + T.unlines [ "\\begin{tabular}{|c|}" + , "One\\\\" + , "Two\\\\" + , "Three\\\\" + , "\\end{tabular}" ] =?> + simpleTable' [AlignCenter] + [[plain "One"], [plain "Two"], [plain "Three"]] + , "Empty table" =: + "\\begin{tabular}{}\\end{tabular}" =?> + simpleTable' [] [] + , "Table with fixed column width" =: + "\\begin{tabular}{|p{5cm}r|}One & Two\\\\ \\end{tabular}" =?> + simpleTable' [AlignLeft,AlignRight] [[plain "One", plain "Two"]] + , "Table with empty column separators" =: + "\\begin{tabular}{@{}r@{}l}One & Two\\\\ \\end{tabular}" =?> + simpleTable' [AlignRight,AlignLeft] [[plain "One", plain "Two"]] + , "Table with custom column separators" =: + T.unlines [ "\\begin{tabular}{@{($\\to$)}r@{\\hspace{2cm}}l}" + , "One&Two\\\\" + , "\\end{tabular}" ] =?> + simpleTable' [AlignRight,AlignLeft] [[plain "One", plain "Two"]] + , "Table with vertical alignment argument" =: + "\\begin{tabular}[t]{r|r}One & Two\\\\ \\end{tabular}" =?> + simpleTable' [AlignRight,AlignRight] [[plain "One", plain "Two"]] + ] + + , testGroup "citations" + [ natbibCitations + , biblatexCitations + ] + + , testGroup "images" + [ "Basic image" =: + "\\includegraphics{foo.png}" =?> + para (image "foo.png" "" (text "image")) + , "Basic image with blank options" =: + "\\includegraphics[]{foo.png}" =?> + para (image "foo.png" "" (text "image")) + , "Image with both width and height" =: + "\\includegraphics[width=17cm,height=5cm]{foo.png}" =?> + para (imageWith ("", [], [("width", "17cm"), ("height", "5cm")]) "foo.png" "" "image") + , "Image with width and height and a bunch of other options" =: + "\\includegraphics[width=17cm,height=5cm,clip,keepaspectratio]{foo.png}" =?> + para (imageWith ("", [], [("width", "17cm"), ("height", "5cm")]) "foo.png" "" "image") + , "Image with just width" =: + "\\includegraphics[width=17cm]{foo.png}" =?> + para (imageWith ("", [], [("width", "17cm")]) "foo.png" "" "image") + , "Image with just height" =: + "\\includegraphics[height=17cm]{foo.png}" =?> + para (imageWith ("", [], [("height", "17cm")]) "foo.png" "" "image") + , "Image width relative to textsize" =: + "\\includegraphics[width=0.6\\textwidth]{foo.png}" =?> + para (imageWith ("", [], [("width", "60%")]) "foo.png" "" "image") + , "Image with options with spaces" =: + "\\includegraphics[width=12cm, height = 5cm]{foo.png}" =?> + para (imageWith ("", [], [("width", "12cm"), ("height", "5cm")]) "foo.png" "" "image") + ] + + , let hex = ['0'..'9']++['a'..'f'] in + testGroup "Character Escapes" + [ "Two-character escapes" =: + mconcat ["^^" <> T.pack [i,j] | i <- hex, j <- hex] =?> + para (str ['\0'..'\255']) + , "One-character escapes" =: + mconcat ["^^" <> T.pack [i] | i <- hex] =?> + para (str $ ['p'..'y']++['!'..'&']) + ] + , testGroup "memoir scene breaks" + [ "plainbreak" =: + "hello\\plainbreak{2}goodbye" =?> + para (str "hello") <> horizontalRule <> para (str "goodbye") + , "plainbreak*" =: + "hello\\plainbreak*{2}goodbye" =?> + para (str "hello") <> horizontalRule <> para (str "goodbye") + , "fancybreak" =: + "hello\\fancybreak{b r e a k}goodbye" =?> + para (str "hello") <> horizontalRule <> para (str "goodbye") + , "fancybreak*" =: + "hello\\fancybreak*{b r e a k}goodbye" =?> + para (str "hello") <> horizontalRule <> para (str "goodbye") + , "plainfancybreak" =: + "hello\\plainfancybreak{4}{2}{b r e a k}goodbye" =?> + para (str "hello") <> horizontalRule <> para (str "goodbye") + , "plainfancybreak*" =: + "hello\\plainfancybreak*{4}{2}{b r e a k}goodbye" =?> + para (str "hello") <> horizontalRule <> para (str "goodbye") + , "pfbreak" =: + "hello\\pfbreak{}goodbye" =?> + para (str "hello") <> horizontalRule <> para (str "goodbye") + , "pfbreak*" =: + "hello\\pfbreak*{}goodbye" =?> + para (str "hello") <> horizontalRule <> para (str "goodbye") + ] + , testGroup "biblatex roman numerals" + [ "upper" =: + "number \\RN{12}" =?> + para (str "number" <> space <> str "XII") + , "lower" =: + "number \\Rn{29}" =?> + para (str "number" <> space <> str "xxix") + , "leading zero" =: + "\\Rn{014}" =?> + para (str "xiv") + , "surrounding spaces" =: + "number \\Rn{ 41 }" =?> + para (str "number" <> space <> str "xli") + , "zero" =: + "\\RN{0}" =?> + para (str "") + , "space then unbraced argument" =: + "\\RN 7 ok" =?> + para (str "VII" <> space <> str "ok") + , "space before braced argument" =: + "\\Rn {13}ok" =?> + para (str "xiiiok") + ] + , testGroup "polyglossia language spans" + [ "french" =: + "hello \\textfrench{bonjour}" =?> + para (str "hello" <> space <> spanWith ("", [], [("lang", "fr")]) (str "bonjour")) + , "nested" =: + "\\textfrench{quelle c'est \\textlatin{primus}?}" =?> + para (spanWith ("", [], [("lang", "fr")]) $ + str "quelle" <> space <> str "c\8217est" <> space <> + spanWith ("", [], [("lang", "la")]) (str "primus") <> str "?") + , "with formatting" =: + "\\textgerman{wie \\emph{spaet} ist es?}" =?> + para (spanWith ("", [], [("lang", "de")]) $ + str "wie" <> space <> emph (str "spaet") <> space <> str "ist" <> space <> str "es?") + , "language options" =: + "\\textgerman[variant=swiss]{hoechdeutsche}" =?> + para (spanWith ("", [], [("lang", "de-CH")]) $ str "hoechdeutsche") + , "unknown option fallback" =: + "\\textgerman[variant=moon]{ueberhoechdeutsche}" =?> + para (spanWith ("", [], [("lang", "de")]) $ str "ueberhoechdeutsche") + ] + ] + +baseCitation :: Citation +baseCitation = Citation{ citationId = "item1" + , citationPrefix = [] + , citationSuffix = [] + , citationMode = AuthorInText + , citationNoteNum = 0 + , citationHash = 0 + } + +rt :: String -> Inlines +rt = rawInline "latex" + +natbibCitations :: TestTree +natbibCitations = testGroup "natbib" + [ "citet" =: "\\citet{item1}" + =?> para (cite [baseCitation] (rt "\\citet{item1}")) + , "suffix" =: "\\citet[p.~30]{item1}" + =?> para + (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" }] (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"] + , citationId = "item2" } + ,baseCitation{ citationId = "item3" + , citationPrefix = [Str "see",Space,Str "also"] + , citationMode = NormalCitation } + ] (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\8211\&35"] } + ,baseCitation{ citationMode = NormalCitation + , citationId = "item3" + , citationPrefix = [Str "also"] + , citationSuffix = [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\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" }] (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 }] (rt "\\citeyearpar{item1}") <> + text ", and now Doe with a locator " <> + cite [baseCitation{ citationMode = SuppressAuthor + , citationSuffix = [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"]] }] (rt "\\citep[\\emph{see}][p. \\textbf{32}]{item1}")) + ] + +biblatexCitations :: TestTree +biblatexCitations = testGroup "biblatex" + [ "textcite" =: "\\textcite{item1}" + =?> para (cite [baseCitation] (rt "\\textcite{item1}")) + , "suffix" =: "\\textcite[p.~30]{item1}" + =?> para + (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" }] (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"] + , citationId = "item2" } + ,baseCitation{ citationId = "item3" + , citationPrefix = [Str "see",Space,Str "also"] + , citationMode = NormalCitation } + ] (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\8211\&35"] } + ,baseCitation{ citationMode = NormalCitation + , citationId = "item3" + , citationPrefix = [Str "also"] + , citationSuffix = [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\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" }] (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 }] (rt "\\autocite*{item1}") <> + text ", and now Doe with a locator " <> + cite [baseCitation{ citationMode = SuppressAuthor + , citationSuffix = [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"]] }] (rt "\\autocite[\\emph{see}][p. \\textbf{32}]{item1}")) + , "parencite" =: "\\parencite{item1}" + =?> para (cite [baseCitation{ citationMode = NormalCitation }] (rt "\\parencite{item1}")) + ] diff --git a/test/Tests/Readers/Markdown.hs.orig b/test/Tests/Readers/Markdown.hs.orig new file mode 100644 index 000000000..1cd32b87d --- /dev/null +++ b/test/Tests/Readers/Markdown.hs.orig @@ -0,0 +1,462 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Readers.Markdown (tests) where + +import Data.Text (Text, unpack) +import qualified Data.Text as T +import Test.Tasty +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder + +markdown :: Text -> Pandoc +markdown = purely $ readMarkdown def { readerExtensions = + disableExtension Ext_smart pandocExtensions } + +markdownSmart :: Text -> Pandoc +markdownSmart = purely $ readMarkdown def { readerExtensions = + enableExtension Ext_smart pandocExtensions } + +markdownCDL :: Text -> Pandoc +markdownCDL = purely $ readMarkdown def { readerExtensions = enableExtension + Ext_compact_definition_lists pandocExtensions } + +markdownGH :: Text -> Pandoc +markdownGH = purely $ readMarkdown def { + readerExtensions = githubMarkdownExtensions } + +infix 4 =: +(=:) :: ToString c + => String -> (Text, c) -> TestTree +(=:) = test markdown + +testBareLink :: (Text, Inlines) -> TestTree +testBareLink (inp, ils) = + test (purely $ readMarkdown def{ readerExtensions = + extensionsFromList [Ext_autolink_bare_uris, Ext_raw_html] }) + (unpack inp) (inp, doc $ para ils) + +autolink :: String -> Inlines +autolink = autolinkWith nullAttr + +autolinkWith :: Attr -> String -> Inlines +autolinkWith attr s = linkWith attr s "" (str s) + +bareLinkTests :: [(Text, Inlines)] +bareLinkTests = + [ ("http://google.com is a search engine.", + autolink "http://google.com" <> " is a search engine.") + , ("
http://foo.bar.baz", + rawInline "html" "" <> + "http://foo.bar.baz" <> rawInline "html" "") + , ("Try this query: http://google.com?search=fish&time=hour.", + "Try this query: " <> autolink "http://google.com?search=fish&time=hour" <> ".") + , ("HTTPS://GOOGLE.COM,", + autolink "HTTPS://GOOGLE.COM" <> ",") + , ("http://el.wikipedia.org/wiki/Τεχνολογία,", + autolink "http://el.wikipedia.org/wiki/Τεχνολογία" <> ",") + , ("doi:10.1000/182,", + autolink "doi:10.1000/182" <> ",") + , ("git://github.com/foo/bar.git,", + autolink "git://github.com/foo/bar.git" <> ",") + , ("file:///Users/joe/joe.txt, and", + autolink "file:///Users/joe/joe.txt" <> ", and") + , ("mailto:someone@somedomain.com.", + autolink "mailto:someone@somedomain.com" <> ".") + , ("Use http: this is not a link!", + "Use http: this is not a link!") + , ("(http://google.com).", + "(" <> autolink "http://google.com" <> ").") + , ("http://en.wikipedia.org/wiki/Sprite_(computer_graphics)", + autolink "http://en.wikipedia.org/wiki/Sprite_(computer_graphics)") + , ("http://en.wikipedia.org/wiki/Sprite_[computer_graphics]", + link "http://en.wikipedia.org/wiki/Sprite_%5Bcomputer_graphics%5D" "" + (str "http://en.wikipedia.org/wiki/Sprite_[computer_graphics]")) + , ("http://en.wikipedia.org/wiki/Sprite_{computer_graphics}", + link "http://en.wikipedia.org/wiki/Sprite_%7Bcomputer_graphics%7D" "" + (str "http://en.wikipedia.org/wiki/Sprite_{computer_graphics}")) + , ("http://example.com/Notification_Center-GitHub-20101108-140050.jpg", + autolink "http://example.com/Notification_Center-GitHub-20101108-140050.jpg") + , ("https://github.com/github/hubot/blob/master/scripts/cream.js#L20-20", + autolink "https://github.com/github/hubot/blob/master/scripts/cream.js#L20-20") + , ("http://www.rubyonrails.com", + autolink "http://www.rubyonrails.com") + , ("http://www.rubyonrails.com:80", + autolink "http://www.rubyonrails.com:80") + , ("http://www.rubyonrails.com/~minam", + autolink "http://www.rubyonrails.com/~minam") + , ("https://www.rubyonrails.com/~minam", + autolink "https://www.rubyonrails.com/~minam") + , ("http://www.rubyonrails.com/~minam/url%20with%20spaces", + autolink "http://www.rubyonrails.com/~minam/url%20with%20spaces") + , ("http://www.rubyonrails.com/foo.cgi?something=here", + autolink "http://www.rubyonrails.com/foo.cgi?something=here") + , ("http://www.rubyonrails.com/foo.cgi?something=here&and=here", + autolink "http://www.rubyonrails.com/foo.cgi?something=here&and=here") + , ("http://www.rubyonrails.com/contact;new", + autolink "http://www.rubyonrails.com/contact;new") + , ("http://www.rubyonrails.com/contact;new%20with%20spaces", + autolink "http://www.rubyonrails.com/contact;new%20with%20spaces") + , ("http://www.rubyonrails.com/contact;new?with=query&string=params", + autolink "http://www.rubyonrails.com/contact;new?with=query&string=params") + , ("http://www.rubyonrails.com/~minam/contact;new?with=query&string=params", + autolink "http://www.rubyonrails.com/~minam/contact;new?with=query&string=params") + , ("http://en.wikipedia.org/wiki/Wikipedia:Today%27s_featured_picture_%28animation%29/January_20%2C_2007", + autolink "http://en.wikipedia.org/wiki/Wikipedia:Today%27s_featured_picture_%28animation%29/January_20%2C_2007") + , ("http://www.mail-archive.com/rails@lists.rubyonrails.org/", + autolink "http://www.mail-archive.com/rails@lists.rubyonrails.org/") + , ("http://www.amazon.com/Testing-Equal-Sign-In-Path/ref=pd_bbs_sr_1?ie=UTF8&s=books&qid=1198861734&sr=8-1", + autolink "http://www.amazon.com/Testing-Equal-Sign-In-Path/ref=pd_bbs_sr_1?ie=UTF8&s=books&qid=1198861734&sr=8-1") + , ("http://en.wikipedia.org/wiki/Texas_hold%27em", + autolink "http://en.wikipedia.org/wiki/Texas_hold%27em") + , ("https://www.google.com/doku.php?id=gps:resource:scs:start", + autolink "https://www.google.com/doku.php?id=gps:resource:scs:start") + , ("http://www.rubyonrails.com", + autolink "http://www.rubyonrails.com") + , ("http://manuals.ruby-on-rails.com/read/chapter.need_a-period/103#page281", + autolink "http://manuals.ruby-on-rails.com/read/chapter.need_a-period/103#page281") + , ("http://foo.example.com/controller/action?parm=value&p2=v2#anchor123", + autolink "http://foo.example.com/controller/action?parm=value&p2=v2#anchor123") + , ("http://foo.example.com:3000/controller/action", + autolink "http://foo.example.com:3000/controller/action") + , ("http://foo.example.com:3000/controller/action+pack", + autolink "http://foo.example.com:3000/controller/action+pack") + , ("http://business.timesonline.co.uk/article/0,,9065-2473189,00.html", + autolink "http://business.timesonline.co.uk/article/0,,9065-2473189,00.html") + , ("http://www.mail-archive.com/ruby-talk@ruby-lang.org/", + autolink "http://www.mail-archive.com/ruby-talk@ruby-lang.org/") + , ("https://example.org/?anchor=lala-", + autolink "https://example.org/?anchor=lala-") + , ("https://example.org/?anchor=-lala", + autolink "https://example.org/?anchor=-lala") + ] + +{- +p_markdown_round_trip :: Block -> Bool +p_markdown_round_trip b = matches d' d'' + where d' = normalize $ Pandoc (Meta [] [] []) [b] + d'' = normalize + $ readMarkdown def { readerSmart = True } + $ writeMarkdown def d' + matches (Pandoc _ [Plain []]) (Pandoc _ []) = True + matches (Pandoc _ [Para []]) (Pandoc _ []) = True + matches (Pandoc _ [Plain xs]) (Pandoc _ [Para xs']) = xs == xs' + matches x y = x == y +-} + +tests :: [TestTree] +tests = [ testGroup "inline code" + [ "with attribute" =: + "`document.write(\"Hello\");`{.javascript}" + =?> para + (codeWith ("",["javascript"],[]) "document.write(\"Hello\");") + , "with attribute space" =: + "`*` {.haskell .special x=\"7\"}" + =?> para (code "*" <> space <> str "{.haskell" <> space <> + str ".special" <> space <> str "x=\"7\"}") + ] + , testGroup "emph and strong" + [ "two strongs in emph" =: + "***a**b **c**d*" =?> para (emph (strong (str "a") <> str "b" <> space + <> strong (str "c") <> str "d")) + , "emph and strong emph alternating" =: + "*xxx* ***xxx*** xxx\n*xxx* ***xxx*** xxx" + =?> para (emph "xxx" <> space <> strong (emph "xxx") <> + space <> "xxx" <> softbreak <> + emph "xxx" <> space <> strong (emph "xxx") <> + space <> "xxx") + , "emph with spaced strong" =: + "*x **xx** x*" + =?> para (emph ("x" <> space <> strong "xx" <> space <> "x")) + , "intraword underscore with opening underscore (#1121)" =: + "_foot_ball_" =?> para (emph (text "foot_ball")) + ] + , testGroup "raw LaTeX" + [ "in URL" =: + "\\begin\n" =?> para (text "\\begin") + ] + , testGroup "raw HTML" + [ "nesting (issue #1330)" =: + "test" =?> + rawBlock "html" "" <> plain (str "test") <> + rawBlock "html" "" + , "invalid tag (issue #1820" =: + "" =?> + para (text "") + , "technically invalid comment" =: + "" =?> + rawBlock "html" "" + , test markdownGH "issue 2469" $ + "<\n\na>" =?> + para (text "<") <> para (text "a>") + ] + , testGroup "raw email addresses" + [ test markdownGH "issue 2940" $ + "**@user**" =?> + para (strong (text "@user")) + ] + , testGroup "emoji" + [ test markdownGH "emoji symbols" $ + ":smile: and :+1:" =?> para (text "😄 and 👍") + ] + , "unbalanced brackets" =: + "[[[[[[[[[[[[hi" =?> para (text "[[[[[[[[[[[[hi") + , 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 "bare URIs" + (map testBareLink bareLinkTests) + , testGroup "autolinks" + [ "with unicode dash following" =: + "\8212" =?> para (autolink "http://foo.bar" <> + str "\8212") + , "a partial URL (#2277)" =: + "" =?> + para (text "") + , "with some attributes" =: + "{#i .j .z k=v}" =?> + para (autolinkWith ("i", ["j", "z"], [("k", "v")]) "http://foo.bar") + , "with some attributes and spaces" =: + " {#i .j .z k=v}" =?> + para (autolink "http://foo.bar" <> space <> text "{#i .j .z k=v}") + ] + , testGroup "links" + [ "no autolink inside link" =: + "[](url)" =?> + para (link "url" "" (text "")) + , "no inline link inside link" =: + "[[a](url2)](url)" =?> + para (link "url" "" (text "[a](url2)")) + , "no bare URI inside link" =: + "[https://example.org(](url)" =?> + para (link "url" "" (text "https://example.org(")) + ] + , testGroup "Headers" + [ "blank line before header" =: + "\n# Header\n" + =?> headerWith ("header",[],[]) 1 "Header" + , "bracketed text (#2062)" =: + "# [hi]\n" + =?> headerWith ("hi",[],[]) 1 "[hi]" + , "ATX header without trailing #s" =: + "# Foo bar\n\n" =?> + headerWith ("foo-bar",[],[]) 1 "Foo bar" + , "ATX header without trailing #s" =: + "# Foo bar with # #" =?> + headerWith ("foo-bar-with",[],[]) 1 "Foo bar with #" + , "setext header" =: + "Foo bar\n=\n\n Foo bar 2 \n=" =?> + headerWith ("foo-bar",[],[]) 1 "Foo bar" + <> headerWith ("foo-bar-2",[],[]) 1 "Foo bar 2" + ] + , testGroup "Implicit header references" + [ "ATX header without trailing #s" =: + "# Header\n[header]\n\n[header ]\n\n[ header]" =?> + headerWith ("header",[],[]) 1 "Header" + <> para (link "#header" "" (text "header")) + <> para (link "#header" "" (text "header")) + <> para (link "#header" "" (text "header")) + , "ATX header with trailing #s" =: + "# Foo bar #\n[foo bar]\n\n[foo bar ]\n\n[ foo bar]" =?> + headerWith ("foo-bar",[],[]) 1 "Foo bar" + <> para (link "#foo-bar" "" (text "foo bar")) + <> para (link "#foo-bar" "" (text "foo bar")) + <> para (link "#foo-bar" "" (text "foo bar")) + , "setext header" =: + " Header \n=\n\n[header]\n\n[header ]\n\n[ header]" =?> + headerWith ("header",[],[]) 1 "Header" + <> para (link "#header" "" (text "header")) + <> para (link "#header" "" (text "header")) + <> para (link "#header" "" (text "header")) + ] + , testGroup "smart punctuation" + [ test markdownSmart "quote before 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»") + , test markdownSmart "apostrophe after math" $ -- issue #1909 + "The value of the $x$'s and the systems' condition." =?> + para (text "The value of the " <> math "x" <> text "\8217s and the systems\8217 condition.") + ] + , 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" + , "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")) + , "recursive note" =: + "[^1]\n\n[^1]: See [^1]\n" + =?> para (note (para "See [^1]")) + ] + , testGroup "lhs" + [ test (purely $ readMarkdown def{ readerExtensions = enableExtension + Ext_literate_haskell pandocExtensions }) + "inverse bird tracks and html" $ + "> a\n\n< b\n\n
\n" + =?> codeBlockWith ("",["sourceCode","literate","haskell"],[]) "a" + <> + codeBlockWith ("",["sourceCode","haskell"],[]) "b" + <> + rawBlock "html" "
\n\n" + ] +-- the round-trip properties frequently fail +-- , testGroup "round trip" +-- [ property "p_markdown_round_trip" p_markdown_round_trip +-- ] + , testGroup "definition lists" + [ "no blank space" =: + "foo1\n : bar\n\nfoo2\n : bar2\n : bar3\n" =?> + definitionList [ (text "foo1", [plain (text "bar")]) + , (text "foo2", [plain (text "bar2"), + plain (text "bar3")]) + ] + , "blank space before first def" =: + "foo1\n\n : bar\n\nfoo2\n\n : bar2\n : bar3\n" =?> + definitionList [ (text "foo1", [para (text "bar")]) + , (text "foo2", [para (text "bar2"), + plain (text "bar3")]) + ] + , "blank space before second def" =: + "foo1\n : bar\n\nfoo2\n : bar2\n\n : bar3\n" =?> + definitionList [ (text "foo1", [plain (text "bar")]) + , (text "foo2", [plain (text "bar2"), + para (text "bar3")]) + ] + , "laziness" =: + "foo1\n : bar\nbaz\n : bar2\n" =?> + definitionList [ (text "foo1", [plain (text "bar" <> + softbreak <> text "baz"), + plain (text "bar2")]) + ] + , "no blank space before first of two paragraphs" =: + "foo1\n : bar\n\n baz\n" =?> + definitionList [ (text "foo1", [para (text "bar") <> + para (text "baz")]) + ] + , "first line not indented" =: + "foo\n: bar\n" =?> + definitionList [ (text "foo", [plain (text "bar")]) ] + , "list in definition" =: + "foo\n: - bar\n" =?> + definitionList [ (text "foo", [bulletList [plain (text "bar")]]) ] + , "in div" =: + "
foo\n: - bar\n
" =?> + divWith nullAttr (definitionList + [ (text "foo", [bulletList [plain (text "bar")]]) ]) + ] + , testGroup "+compact_definition_lists" + [ test markdownCDL "basic compact list" $ + "foo1\n: bar\n baz\nfoo2\n: bar2\n" =?> + definitionList [ (text "foo1", [plain (text "bar" <> softbreak <> + text "baz")]) + , (text "foo2", [plain (text "bar2")]) + ] + ] + , testGroup "lists" + [ "issue #1154" =: + " -
\n first div breaks\n
\n\n \n\n
\n with this div too.\n
\n" + =?> bulletList [divWith nullAttr (para $ text "first div breaks") <> + rawBlock "html" "" <> + divWith nullAttr (para $ text "with this div too.")] + , test markdownGH "issue #1636" $ + T.unlines [ "* a" + , "* b" + , "* c" + , " * d" ] + =?> + bulletList [ plain "a" + , plain "b" + , plain "c" <> bulletList [plain "d"] ] + ] + , testGroup "entities" + [ "character references" =: + "⟨ ö" =?> para (text "\10216 ö") + , "numeric" =: + ",DD" =?> para (text ",DD") + , "in link title" =: + "[link](/url \"title ⟨ ö ,\")" =?> + para (link "/url" "title \10216 ö ," (text "link")) + ] + , testGroup "citations" + [ "simple" =: + "@item1" =?> para (cite [ + Citation{ citationId = "item1" + , citationPrefix = [] + , citationSuffix = [] + , citationMode = AuthorInText + , citationNoteNum = 0 + , citationHash = 0 + } + ] "@item1") + , "key starts with digit" =: + "@1657:huyghens" =?> para (cite [ + Citation{ citationId = "1657:huyghens" + , citationPrefix = [] + , citationSuffix = [] + , citationMode = AuthorInText + , citationNoteNum = 0 + , citationHash = 0 + } + ] "@1657:huyghens") + ] + , let citation = cite [Citation "cita" [] [] AuthorInText 0 0] (str "@cita") + in testGroup "footnote/link following citation" -- issue #2083 + [ "footnote" =: + T.unlines [ "@cita[^note]" + , "" + , "[^note]: note" ] =?> + para ( + citation <> note (para $ str "note") + ) + , "normal link" =: + "@cita [link](http://www.com)" =?> + para ( + citation <> space <> link "http://www.com" "" (str "link") + ) + , "reference link" =: + T.unlines [ "@cita [link][link]" + , "" + , "[link]: http://www.com" ] =?> + para ( + citation <> space <> link "http://www.com" "" (str "link") + ) + , "short reference link" =: + T.unlines [ "@cita [link]" + , "" + , "[link]: http://www.com" ] =?> + para ( + citation <> space <> link "http://www.com" "" (str "link") + ) + , "implicit header link" =: + T.unlines [ "# Header" + , "@cita [Header]" ] =?> + headerWith ("header",[],[]) 1 (str "Header") <> para ( + citation <> space <> link "#header" "" (str "Header") + ) + , "regular citation" =: + "@cita [foo]" =?> + para ( + cite [Citation "cita" [] [Str "foo"] AuthorInText 0 0] + (str "@cita" <> space <> str "[foo]") + ) + ] + ] diff --git a/test/Tests/Readers/Muse.hs.orig b/test/Tests/Readers/Muse.hs.orig new file mode 100644 index 000000000..89dbbc345 --- /dev/null +++ b/test/Tests/Readers/Muse.hs.orig @@ -0,0 +1,1262 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Readers.Muse (tests) where + +import Data.List (intersperse) +import Data.Text (Text) +import qualified Data.Text as T +import Test.Tasty +import Test.Tasty.QuickCheck +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder +import Text.Pandoc.Shared (underlineSpan) +import Text.Pandoc.Walk (walk) + +amuse :: Text -> Pandoc +amuse = purely $ readMuse def { readerExtensions = extensionsFromList [Ext_amuse]} + +emacsMuse :: Text -> Pandoc +emacsMuse = purely $ readMuse def { readerExtensions = emptyExtensions } + +infix 4 =: +(=:) :: ToString c + => String -> (Text, c) -> TestTree +(=:) = test amuse + +spcSep :: [Inlines] -> Inlines +spcSep = mconcat . intersperse space + +-- Tables don't round-trip yet +-- +makeRoundTrip :: Block -> Block +makeRoundTrip Table{} = Para [Str "table was here"] +makeRoundTrip (OrderedList (start, LowerAlpha, _) items) = OrderedList (start, Decimal, Period) items +makeRoundTrip (OrderedList (start, UpperAlpha, _) items) = OrderedList (start, Decimal, Period) items +makeRoundTrip x = x + +-- Demand that any AST produced by Muse reader and written by Muse writer can be read back exactly the same way. +-- Currently we remove tables and compare first rewrite to the second. +roundTrip :: Block -> Bool +roundTrip b = d' == d'' + where d = walk makeRoundTrip $ Pandoc nullMeta [b] + d' = rewrite d + d'' = rewrite d' + rewrite = amuse . T.pack . (++ "\n") . T.unpack . + purely (writeMuse def { writerExtensions = extensionsFromList [Ext_amuse] + , writerWrapText = WrapPreserve + }) + +tests :: [TestTree] +tests = + [ testGroup "Inlines" + [ "Plain String" =: + "Hello, World" =?> + para "Hello, World" + + , "Muse is not XML" =: "<" =?> para "<" + + , "Emphasis" =: + "*Foo bar*" =?> + para (emph . spcSep $ ["Foo", "bar"]) + + , "Comma after closing *" =: + "Foo *bar*, baz" =?> + para ("Foo " <> emph "bar" <> ", baz") + + , "Letter after closing *" =: + "Foo *bar*x baz" =?> + para "Foo *bar*x baz" + + , "Letter before opening *" =: + "Foo x*bar* baz" =?> + para "Foo x*bar* baz" + + , "Emphasis tag" =: + "Foo bar" =?> + para (emph . spcSep $ ["Foo", "bar"]) + + , "Strong" =: + "**Cider**" =?> + para (strong "Cider") + + , "Strong tag" =: "Strong" =?> para (strong "Strong") + + , "Strong Emphasis" =: + "***strength***" =?> + para (strong . emph $ "strength") + + , test emacsMuse "Underline" + ("_Underline_" =?> para (underlineSpan "Underline")) + + , "Superscript tag" =: "Superscript" =?> para (superscript "Superscript") + + , "Subscript tag" =: "Subscript" =?> para (subscript "Subscript") + + , "Strikeout tag" =: "Strikeout" =?> para (strikeout "Strikeout") + + , "Opening inline tags" =: "foo bar baz" =?> para "foo bar baz" + + , "Closing inline tags" =: "foo bar baz" =?> para "foo bar baz" + + , "Tag soup" =: "foo bar baz" =?> para "foo bar
baz" + + -- Both inline tags must be within the same paragraph + , "No multiparagraph inline tags" =: + T.unlines [ "First line" + , "Second line" + , "" + , "Fourth line" + ] =?> + para "First line\nSecond line" <> + para "Fourth line" + + , "Linebreak" =: "Line
break" =?> para ("Line" <> linebreak <> "break") + + , "Trailing whitespace inside paragraph" =: + T.unlines [ "First line " -- trailing whitespace here + , "second line" + ] + =?> para "First line\nsecond line" + + , "Non-breaking space" =: "Foo~~bar" =?> para "Foo\160bar" + , "Single ~" =: "Foo~bar" =?> para "Foo~bar" + + , testGroup "Code markup" + [ "Code" =: "=foo(bar)=" =?> para (code "foo(bar)") + + , "Not code" =: "a=b= =c=d" =?> para (text "a=b= =c=d") + + -- Emacs Muse 3.20 parses this as code, we follow Amusewiki + , "Not code if closing = is detached" =: "=this is not a code =" =?> para "=this is not a code =" + + , "Not code if opening = is detached" =: "= this is not a code=" =?> para "= this is not a code=" + + , "Code if followed by comma" =: + "Foo =bar=, baz" =?> + para (text "Foo " <> code "bar" <> text ", baz") + + , "One character code" =: "=c=" =?> para (code "c") + + , "Three = characters is not a code" =: "===" =?> para "===" + + , "Multiline code markup" =: + "foo =bar\nbaz= end of code" =?> + para (text "foo " <> code "bar\nbaz" <> text " end of code") + +{- Emacs Muse 3.20 has a bug: it publishes + -

foo bar + - + - baz foo

+ - which is displayed as one paragraph by browsers. + - We follow Amusewiki here and avoid joining paragraphs. + -} + , "No multiparagraph code" =: + T.unlines [ "foo =bar" + , "" + , "baz= foo" + ] =?> + para "foo =bar" <> + para "baz= foo" + + , "Code at the beginning of paragraph but not first column" =: + " - =foo=" =?> bulletList [ para $ code "foo" ] + ] + + , "Code tag" =: "foo(bar)" =?> para (code "foo(bar)") + + , "Verbatim tag" =: "***" =?> para (emph "*") + + , "Verbatim inside code" =: "foo" =?> para (code "foo") + + , "Verbatim tag after text" =: "Foo bar" =?> para "Foo bar" + + , "Class tag" =: "bar" =?> para (spanWith ("", ["foo"], []) "bar") + , "Class tag without name" =: "foobar" =?> para (spanWith ("", [], []) "foobar") + + -- tag should match with the last tag, not verbatim one + , "Nested \"
\" inside em tag" =: "foobar
" =?> para (emph "foobar") + + , testGroup "Links" + [ "Link without description" =: + "[[https://amusewiki.org/]]" =?> + para (link "https://amusewiki.org/" "" (str "https://amusewiki.org/")) + , "Link with description" =: + "[[https://amusewiki.org/][A Muse Wiki]]" =?> + para (link "https://amusewiki.org/" "" (text "A Muse Wiki")) + , "Image" =: + "[[image.jpg]]" =?> + para (image "image.jpg" "" mempty) + , "Image with description" =: + "[[image.jpg][Image]]" =?> + para (image "image.jpg" "" (text "Image")) + , "Image link" =: + "[[URL:image.jpg]]" =?> + para (link "image.jpg" "" (str "image.jpg")) + , "Image link with description" =: + "[[URL:image.jpg][Image]]" =?> + para (link "image.jpg" "" (text "Image")) + -- Implicit links are supported in Emacs Muse, but not in Amusewiki: + -- https://github.com/melmothx/text-amuse/issues/18 + -- + -- This test also makes sure '=' without whitespace is not treated as code markup + , "No implicit links" =: "http://example.org/index.php?action=view&id=1" + =?> para "http://example.org/index.php?action=view&id=1" + ] + + , testGroup "Literal" + [ test emacsMuse "Inline literal" + ("Foolitbar" =?> + para (text "Foo" <> rawInline "html" "lit" <> text "bar")) + ] + ] + + , testGroup "Blocks" + [ testProperty "Round trip" roundTrip, + "Block elements end paragraphs" =: + T.unlines [ "First paragraph" + , "----" + , "Second paragraph" + ] =?> para (text "First paragraph") <> horizontalRule <> para (text "Second paragraph") + , testGroup "Horizontal rule" + [ "Less than 4 dashes is not a horizontal rule" =: "---" =?> para (text "---") + , "4 dashes is a horizontal rule" =: "----" =?> horizontalRule + , "5 dashes is a horizontal rule" =: "-----" =?> horizontalRule + , "4 dashes with spaces is a horizontal rule" =: "---- " =?> horizontalRule + ] + , testGroup "Paragraphs" + [ "Simple paragraph" =: + T.unlines [ "First line" + , "second line." + ] =?> + para "First line\nsecond line." + , "Indented paragraph" =: + T.unlines [ " First line" + , "second line." + ] =?> + para "First line\nsecond line." + -- Emacs Muse starts a blockquote on the second line. + -- We copy Amusewiki behavior and require a blank line to start a blockquote. + , "Indentation in the middle of paragraph" =: + T.unlines [ "First line" + , " second line" + , "third line" + ] =?> + para "First line\nsecond line\nthird line" + , "Quote" =: + " This is a quotation\n" =?> + blockQuote (para "This is a quotation") + , "Indentation does not indicate quote inside quote tag" =: + T.unlines [ "" + , " Not a nested quote" + , "" + ] =?> + blockQuote (para "Not a nested quote") + , "Multiline quote" =: + T.unlines [ " This is a quotation" + , " with a continuation" + ] =?> + blockQuote (para "This is a quotation\nwith a continuation") + , testGroup "Div" + [ "Div without id" =: + T.unlines [ "
" + , "Foo bar" + , "
" + ] =?> + divWith nullAttr (para "Foo bar") + , "Div with id" =: + T.unlines [ "
" + , "Foo bar" + , "
" + ] =?> + divWith ("foo", [], []) (para "Foo bar") + ] + , "Verse" =: + T.unlines [ "> This is" + , "> First stanza" + , ">" -- Emacs produces verbatim ">" here, we follow Amusewiki + , "> And this is" + , "> Second stanza" + , ">" + , "" + , ">" + , "" + , "> Another verse" + , "> is here" + ] =?> + lineBlock [ "This is" + , "First stanza" + , "" + , "And this is" + , "\160\160Second stanza" + , "" + ] <> + lineBlock [ "" ] <> + lineBlock [ "Another verse" + , "\160\160\160is here" + ] + ] + , "Verse in list" =: " - > foo" =?> bulletList [ lineBlock [ "foo" ] ] + , "Verse line starting with emphasis" =: "> *foo* bar" =?> lineBlock [ emph "foo" <> text " bar" ] + , "Multiline verse in list" =: + T.unlines [ " - > foo" + , " > bar" + ] =?> + bulletList [ lineBlock [ "foo", "bar" ] ] + , "Paragraph after verse in list" =: + T.unlines [ " - > foo" + , " bar" + ] =?> + bulletList [ lineBlock [ "foo" ] <> para "bar" ] + , "Empty quote tag" =: + T.unlines [ "" + , "" + ] + =?> blockQuote mempty + , "Quote tag" =: + T.unlines [ "" + , "Hello, world" + , "" + ] + =?> blockQuote (para $ text "Hello, world") + , "Nested quote tag" =: + T.unlines [ "" + , "foo" + , "" + , "bar" + , "" + , "baz" + , "" + ] =?> + blockQuote (para "foo" <> blockQuote (para "bar") <> para "baz") + , "Indented quote inside list" =: + T.unlines [ " - " + , " foo" + , " " + ] =?> + bulletList [ blockQuote (para "foo") ] + , "Verse tag" =: + T.unlines [ "" + , "" + , "Foo bar baz" + , " One two three" + , "" + , "" + ] =?> + lineBlock [ "" + , text "Foo bar baz" + , text "\160\160One two three" + , "" + ] + , "Verse tag with empty line inside" =: + T.unlines [ "" + , "" + , "" + ] =?> + lineBlock [ "" ] + , testGroup "Example" + [ "Braces on separate lines" =: + T.unlines [ "{{{" + , "Example line" + , "}}}" + ] =?> + codeBlock "Example line" + , "Spaces after opening braces" =: + T.unlines [ "{{{ " + , "Example line" + , "}}}" + ] =?> + codeBlock "Example line" + , "One blank line in the beginning" =: + T.unlines [ "{{{" + , "" + , "Example line" + , "}}}" + ] =?> + codeBlock "\nExample line" + , "One blank line in the end" =: + T.unlines [ "{{{" + , "Example line" + , "" + , "}}}" + ] =?> + codeBlock "Example line\n" + -- Amusewiki requires braces to be on separate line, + -- this is an extension. + , "One line" =: + "{{{Example line}}}" =?> + codeBlock "Example line" + ] + , testGroup "Example tag" + [ "Tags on separate lines" =: + T.unlines [ "" + , "Example line" + , "" + ] =?> + codeBlock "Example line" + , "One line" =: + "Example line" =?> + codeBlock "Example line" + , "One blank line in the beginning" =: + T.unlines [ "" + , "" + , "Example line" + , "" + ] =?> + codeBlock "\nExample line" + , "One blank line in the end" =: + T.unlines [ "" + , "Example line" + , "" + , "" + ] =?> + codeBlock "Example line\n" + , "Example inside list" =: + T.unlines [ " - " + , " foo" + , " " + ] =?> + bulletList [ codeBlock "foo" ] + , "Empty example inside list" =: + T.unlines [ " - " + , " " + ] =?> + bulletList [ codeBlock "" ] + , "Example inside list with empty lines" =: + T.unlines [ " - " + , " foo" + , " " + , "" + , " bar" + , "" + , " " + , " baz" + , " " + ] =?> + bulletList [ codeBlock "foo" <> para "bar" <> codeBlock "baz" ] + , "Indented example inside list" =: + T.unlines [ " - " + , " foo" + , " " + ] =?> + bulletList [ codeBlock "foo" ] + , "Example inside definition list" =: + T.unlines [ " foo :: " + , " bar" + , " " + ] =?> + definitionList [ ("foo", [codeBlock "bar"]) ] + , "Example inside list definition with empty lines" =: + T.unlines [ " term :: " + , " foo" + , " " + , "" + , " bar" + , "" + , " " + , " baz" + , " " + ] =?> + definitionList [ ("term", [codeBlock "foo" <> para "bar" <> codeBlock "baz"]) ] + , "Example inside note" =: + T.unlines [ "Foo[1]" + , "" + , "[1] " + , " bar" + , " " + ] =?> + para ("Foo" <> note (codeBlock "bar")) + ] + , testGroup "Literal blocks" + [ test emacsMuse "Literal block" + (T.unlines [ "" + , "\\newpage" + , "" + ] =?> + rawBlock "latex" "\\newpage") + ] + , "Center" =: + T.unlines [ "
" + , "Hello, world" + , "
" + ] =?> + para (text "Hello, world") + , "Right" =: + T.unlines [ "" + , "Hello, world" + , "" + ] =?> + para (text "Hello, world") + , testGroup "Comments" + [ "Comment tag" =: "\nThis is a comment\n" =?> (mempty::Blocks) + , "Line comment" =: "; Comment" =?> (mempty::Blocks) + , "Empty comment" =: ";" =?> (mempty::Blocks) + , "Text after empty comment" =: ";\nfoo" =?> para "foo" -- Make sure we don't consume newline while looking for whitespace + , "Not a comment (does not start with a semicolon)" =: " ; Not a comment" =?> para (text "; Not a comment") + , "Not a comment (has no space after semicolon)" =: ";Not a comment" =?> para (text ";Not a comment") + ] + , testGroup "Headers" + [ "Part" =: + "* First level" =?> + header 1 "First level" + , "Chapter" =: + "** Second level" =?> + header 2 "Second level" + , "Section" =: + "*** Third level" =?> + header 3 "Third level" + , "Subsection" =: + "**** Fourth level" =?> + header 4 "Fourth level" + , "Subsubsection" =: + "***** Fifth level" =?> + header 5 "Fifth level" + , "Whitespace is required after *" =: "**Not a header" =?> para "**Not a header" + , "No headers in footnotes" =: + T.unlines [ "Foo[1]" + , "[1] * Bar" + ] =?> + para (text "Foo" <> + note (para "* Bar")) + , "No headers in quotes" =: + T.unlines [ "" + , "* Hi" + , "" + ] =?> + blockQuote (para "* Hi") + , "Headers consume anchors" =: + T.unlines [ "** Foo" + , "#bar" + ] =?> + headerWith ("bar",[],[]) 2 "Foo" + , "Headers don't consume anchors separated with a blankline" =: + T.unlines [ "** Foo" + , "" + , "#bar" + ] =?> + header 2 "Foo" <> + para (spanWith ("bar", [], []) mempty) + , "Headers terminate lists" =: + T.unlines [ " - foo" + , "* bar" + ] =?> + bulletList [ para "foo" ] <> + header 1 "bar" + ] + , testGroup "Directives" + [ "Title" =: + "#title Document title" =?> + let titleInline = toList "Document title" + meta = setMeta "title" (MetaInlines titleInline) nullMeta + in Pandoc meta mempty + -- Emacs Muse documentation says that "You can use any combination + -- of uppercase and lowercase letters for directives", + -- but also allows '-', which is not documented, but used for disable-tables. + , test emacsMuse "Disable tables" + ("#disable-tables t" =?> + Pandoc (setMeta "disable-tables" (MetaInlines $ toList "t") nullMeta) mempty) + , "Multiple directives" =: + T.unlines [ "#title Document title" + , "#subtitle Document subtitle" + ] =?> + Pandoc (setMeta "title" (MetaInlines $ toList "Document title") $ + setMeta "subtitle" (MetaInlines $ toList "Document subtitle") nullMeta) mempty + , "Multiline directive" =: + T.unlines [ "#title Document title" + , "#notes First line" + , "and second line" + , "#author Name" + ] =?> + Pandoc (setMeta "title" (MetaInlines $ toList "Document title") $ + setMeta "notes" (MetaInlines $ toList "First line\nand second line") $ + setMeta "author" (MetaInlines $ toList "Name") nullMeta) mempty + ] + , testGroup "Anchors" + [ "Anchor" =: + T.unlines [ "; A comment to make sure anchor is not parsed as a directive" + , "#anchor Target" + ] =?> + para (spanWith ("anchor", [], []) mempty <> "Target") + , "Anchor cannot start with a number" =: + T.unlines [ "; A comment to make sure anchor is not parsed as a directive" + , "#0notanchor Target" + ] =?> + para "#0notanchor Target" + , "Not anchor if starts with a space" =: + " #notanchor Target" =?> + para "#notanchor Target" + , "Anchor inside a paragraph" =: + T.unlines [ "Paragraph starts here" + , "#anchor and ends here." + ] =?> + para ("Paragraph starts here\n" <> spanWith ("anchor", [], []) mempty <> "and ends here.") + ] + , testGroup "Footnotes" + [ "Simple footnote" =: + T.unlines [ "Here is a footnote[1]." + , "" + , "[1] Footnote contents" + ] =?> + para (text "Here is a footnote" <> + note (para "Footnote contents") <> + str ".") + , "Recursive footnote" =: + T.unlines [ "Start recursion here[1]" + , "" + , "[1] Recursion continues here[1]" + ] =?> + para (text "Start recursion here" <> + note (para "Recursion continues here[1]")) + , "No zero footnotes" =: + T.unlines [ "Here is a footnote[0]." + , "" + , "[0] Footnote contents" + ] =?> + para "Here is a footnote[0]." <> + para "[0] Footnote contents" + , "Footnotes can't start with zero" =: + T.unlines [ "Here is a footnote[01]." + , "" + , "[01] Footnote contents" + ] =?> + para "Here is a footnote[01]." <> + para "[01] Footnote contents" + , testGroup "Multiparagraph footnotes" + [ "Amusewiki multiparagraph footnotes" =: + T.unlines [ "Multiparagraph[1] footnotes[2]" + , "" + , "[1] First footnote paragraph" + , "" + , " Second footnote paragraph" + , "with continuation" + , "" + , "Not a note" + , "[2] Second footnote" + ] =?> + para (text "Multiparagraph" <> + note (para "First footnote paragraph" <> + para "Second footnote paragraph\nwith continuation") <> + text " footnotes" <> + note (para "Second footnote")) <> + para (text "Not a note") + + -- Verse requires precise indentation, so it is good to test indentation requirements + , "Note continuation with verse" =: + T.unlines [ "Foo[1]" + , "" + , "[1] Bar" + , "" + , " > Baz" + ] =?> + para ("Foo" <> note (para "Bar" <> lineBlock ["Baz"])) + , test emacsMuse "Emacs multiparagraph footnotes" + (T.unlines + [ "First footnote reference[1] and second footnote reference[2]." + , "" + , "[1] First footnote paragraph" + , "" + , "Second footnote" + , "paragraph" + , "" + , "[2] Third footnote paragraph" + , "" + , "Fourth footnote paragraph" + ] =?> + para (text "First footnote reference" <> + note (para "First footnote paragraph" <> + para "Second footnote\nparagraph") <> + text " and second footnote reference" <> + note (para "Third footnote paragraph" <> + para "Fourth footnote paragraph") <> + text ".")) + ] + ] + ] + , testGroup "Tables" + [ "Two cell table" =: + "One | Two" =?> + table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] + [] + [[plain "One", plain "Two"]] + , "Table with multiple words" =: + "One two | three four" =?> + table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] + [] + [[plain "One two", plain "three four"]] + , "Not a table" =: + "One| Two" =?> + para (text "One| Two") + , "Not a table again" =: + "One |Two" =?> + para (text "One |Two") + , "Two line table" =: + T.unlines + [ "One | Two" + , "Three | Four" + ] =?> + table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] + [] + [[plain "One", plain "Two"], + [plain "Three", plain "Four"]] + , "Table with one header" =: + T.unlines + [ "First || Second" + , "Third | Fourth" + ] =?> + table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] + [plain "First", plain "Second"] + [[plain "Third", plain "Fourth"]] + , "Table with two headers" =: + T.unlines + [ "First || header" + , "Second || header" + , "Foo | bar" + ] =?> + table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] + [plain "First", plain "header"] + [[plain "Second", plain "header"], + [plain "Foo", plain "bar"]] + , "Header and footer reordering" =: + T.unlines + [ "Foo ||| bar" + , "Baz || foo" + , "Bar | baz" + ] =?> + table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] + [plain "Baz", plain "foo"] + [[plain "Bar", plain "baz"], + [plain "Foo", plain "bar"]] + , "Table with caption" =: + T.unlines + [ "Foo || bar || baz" + , "First | row | here" + , "Second | row | there" + , "|+ Table caption +|" + ] =?> + table (text "Table caption") (replicate 3 (AlignDefault, 0.0)) + [plain "Foo", plain "bar", plain "baz"] + [[plain "First", plain "row", plain "here"], + [plain "Second", plain "row", plain "there"]] + , "Caption without table" =: + "|+ Foo bar baz +|" =?> + table (text "Foo bar baz") [] [] [] + , "Table indented with space" =: + T.unlines + [ " Foo | bar" + , " Baz | foo" + , " Bar | baz" + ] =?> + table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] + [] + [[plain "Foo", plain "bar"], + [plain "Baz", plain "foo"], + [plain "Bar", plain "baz"]] + , "Empty cells" =: + T.unlines + [ " | Foo" + , " |" + , " bar |" + , " || baz" + ] =?> + table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] + [plain "", plain "baz"] + [[plain "", plain "Foo"], + [plain "", plain ""], + [plain "bar", plain ""]] + ] + , testGroup "Lists" + [ "Bullet list" =: + T.unlines + [ " - Item1" + , "" + , " - Item2" + ] =?> + bulletList [ para "Item1" + , para "Item2" + ] + , "Ordered list" =: + T.unlines + [ " 1. Item1" + , "" + , " 2. Item2" + ] =?> + orderedListWith (1, Decimal, Period) [ para "Item1" + , para "Item2" + ] + , "Ordered list with implicit numbers" =: + T.unlines + [ " 1. Item1" + , "" + , " 1. Item2" + , "" + , " 1. Item3" + ] =?> + orderedListWith (1, Decimal, Period) [ para "Item1" + , para "Item2" + , para "Item3" + ] + , "Ordered list with roman numerals" =: + T.unlines + [ " i. First" + , " ii. Second" + , " iii. Third" + , " iv. Fourth" + ] =?> + orderedListWith (1, LowerRoman, Period) [ para "First" + , para "Second" + , para "Third" + , para "Fourth" + ] + , "Bullet list with empty items" =: + T.unlines + [ " -" + , "" + , " - Item2" + ] =?> + bulletList [ mempty + , para "Item2" + ] + , "Ordered list with empty items" =: + T.unlines + [ " 1." + , "" + , " 2." + , "" + , " 3. Item3" + ] =?> + orderedListWith (1, Decimal, Period) [ mempty + , mempty + , para "Item3" + ] + , "Bullet list with last item empty" =: + T.unlines + [ " -" + , "" + , "foo" + ] =?> + bulletList [ mempty ] <> + para "foo" + , testGroup "Nested lists" + [ "Nested bullet list" =: + T.unlines [ " - Item1" + , " - Item2" + , " - Item3" + , " - Item4" + , " - Item5" + , " - Item6" + ] =?> + bulletList [ para "Item1" <> + bulletList [ para "Item2" <> + bulletList [ para "Item3" ] + , para "Item4" <> + bulletList [ para "Item5" ] + ] + , para "Item6" + ] + , "Nested ordered list" =: + T.unlines [ " 1. Item1" + , " 1. Item2" + , " 1. Item3" + , " 2. Item4" + , " 1. Item5" + , " 2. Item6" + ] =?> + orderedListWith (1, Decimal, Period) [ para "Item1" <> + orderedListWith (1, Decimal, Period) [ para "Item2" <> + orderedListWith (1, Decimal, Period) [ para "Item3" ] + , para "Item4" <> + orderedListWith (1, Decimal, Period) [ para "Item5" ] + ] + , para "Item6" + ] + , "Mixed nested list" =: + T.unlines + [ " - Item1" + , " - Item2" + , " - Item3" + , " - Item4" + , " 1. Nested" + , " 2. Ordered" + , " 3. List" + ] =?> + bulletList [ mconcat [ para "Item1" + , bulletList [ para "Item2" + , para "Item3" + ] + ] + , mconcat [ para "Item4" + , orderedListWith (1, Decimal, Period) [ para "Nested" + , para "Ordered" + , para "List" + ] + ] + ] + , "Text::Amuse includes only one space in list marker" =: + T.unlines + [ " - First item" + , " - Nested item" + ] =?> + bulletList [ para "First item" <> bulletList [ para "Nested item"]] + ] + , "List continuation" =: + T.unlines + [ " - a" + , "" + , " b" + , "" + , " c" + ] =?> + bulletList [ mconcat [ para "a" + , para "b" + , para "c" + ] + ] + , "List continuation afeter nested list" =: + T.unlines + [ " - - foo" + , "" + , " bar" + ] =?> + bulletList [ bulletList [ para "foo" ] <> + para "bar" + ] + -- Emacs Muse allows to separate lists with two or more blank lines. + -- Text::Amuse (Amusewiki engine) always creates a single list as of version 0.82. + -- pandoc follows Emacs Muse behavior + , testGroup "Blank lines" + [ "Blank lines between list items are not required" =: + T.unlines + [ " - Foo" + , " - Bar" + ] =?> + bulletList [ para "Foo" + , para "Bar" + ] + , "One blank line between list items is allowed" =: + T.unlines + [ " - Foo" + , "" + , " - Bar" + ] =?> + bulletList [ para "Foo" + , para "Bar" + ] + , "Two blank lines separate lists" =: + T.unlines + [ " - Foo" + , "" + , "" + , " - Bar" + ] =?> + bulletList [ para "Foo" ] <> bulletList [ para "Bar" ] + , "No blank line after multiline first item" =: + T.unlines + [ " - Foo" + , " bar" + , " - Baz" + ] =?> + bulletList [ para "Foo\nbar" + , para "Baz" + ] + , "One blank line after multiline first item" =: + T.unlines + [ " - Foo" + , " bar" + , "" + , " - Baz" + ] =?> + bulletList [ para "Foo\nbar" + , para "Baz" + ] + , "Two blank lines after multiline first item" =: + T.unlines + [ " - Foo" + , " bar" + , "" + , "" + , " - Baz" + ] =?> + bulletList [ para "Foo\nbar" ] <> bulletList [ para "Baz" ] + , "No blank line after list continuation" =: + T.unlines + [ " - Foo" + , "" + , " bar" + , " - Baz" + ] =?> + bulletList [ para "Foo" <> para "bar" + , para "Baz" + ] + , "One blank line after list continuation" =: + T.unlines + [ " - Foo" + , "" + , " bar" + , "" + , " - Baz" + ] =?> + bulletList [ para "Foo" <> para "bar" + , para "Baz" + ] + , "Two blank lines after list continuation" =: + T.unlines + [ " - Foo" + , "" + , " bar" + , "" + , "" + , " - Baz" + ] =?> + bulletList [ para "Foo" <> para "bar" ] <> bulletList [ para "Baz" ] + , "No blank line after blockquote" =: + T.unlines + [ " - " + , " foo" + , " " + , " - bar" + ] =?> + bulletList [ blockQuote $ para "foo", para "bar" ] + , "One blank line after blockquote" =: + T.unlines + [ " - " + , " foo" + , " " + , "" + , " - bar" + ] =?> + bulletList [ blockQuote $ para "foo", para "bar" ] + , "Two blank lines after blockquote" =: + T.unlines + [ " - " + , " foo" + , " " + , "" + , "" + , " - bar" + ] =?> + bulletList [ blockQuote $ para "foo" ] <> bulletList [ para "bar" ] + , "No blank line after verse" =: + T.unlines + [ " - > foo" + , " - bar" + ] =?> + bulletList [ lineBlock [ "foo" ], para "bar" ] + , "One blank line after verse" =: + T.unlines + [ " - > foo" + , "" + , " - bar" + ] =?> + bulletList [ lineBlock [ "foo" ], para "bar" ] + , "Two blank lines after verse" =: + T.unlines + [ " - > foo" + , "" + , "" + , " - bar" + ] =?> + bulletList [ lineBlock [ "foo" ] ] <> bulletList [ para "bar" ] + ] + -- Test that definition list requires a leading space. + -- Emacs Muse does not require a space, we follow Amusewiki here. + , "Not a definition list" =: + T.unlines + [ "First :: second" + , "Foo :: bar" + ] =?> + para "First :: second\nFoo :: bar" + , test emacsMuse "Emacs Muse definition list" + (T.unlines + [ "First :: second" + , "Foo :: bar" + ] =?> + definitionList [ ("First", [ para "second" ]) + , ("Foo", [ para "bar" ]) + ]) + , "Definition list" =: + T.unlines + [ " First :: second" + , " Foo :: bar" + ] =?> + definitionList [ ("First", [ para "second" ]) + , ("Foo", [ para "bar" ]) + ] + , "Definition list term cannot include newline" =: + T.unlines + [ " Foo" -- "Foo" is not a part of the definition list term + , " Bar :: baz" + ] =?> + para "Foo" <> + definitionList [ ("Bar", [ para "baz" ]) ] + , "One-line definition list" =: " foo :: bar" =?> + definitionList [ ("foo", [ para "bar" ]) ] + , "Definition list term may include single colon" =: + " foo:bar :: baz" =?> + definitionList [ ("foo:bar", [ para "baz" ]) ] + , "Definition list term with emphasis" =: " *Foo* :: bar\n" =?> + definitionList [ (emph "Foo", [ para "bar" ]) ] + , "Definition list term with :: inside code" =: " foo :: :: bar :: baz\n" =?> + definitionList [ ("foo " <> code " :: ", [ para $ "bar " <> code " :: " <> " baz" ]) ] + , "Multi-line definition lists" =: + T.unlines + [ " First term :: Definition of first term" + , "and its continuation." + , " Second term :: Definition of second term." + ] =?> + definitionList [ ("First term", [ para "Definition of first term\nand its continuation." ]) + , ("Second term", [ para "Definition of second term." ]) + ] + , test emacsMuse "Multi-line definition lists from Emacs Muse manual" + (T.unlines + [ "Term1 ::" + , " This is a first definition" + , " And it has two lines;" + , "no, make that three." + , "" + , "Term2 :: This is a second definition" + ] =?> + definitionList [ ("Term1", [ para "This is a first definition\nAnd it has two lines;\nno, make that three."]) + , ("Term2", [ para "This is a second definition"]) + ]) + -- Text::Amuse requires indentation with one space + , "Multi-line definition lists from Emacs Muse manual with initial space" =: + (T.unlines + [ " Term1 ::" + , " This is a first definition" + , " And it has two lines;" + , "no, make that three." + , "" + , " Term2 :: This is a second definition" + ] =?> + definitionList [ ("Term1", [ para "This is a first definition\nAnd it has two lines;\nno, make that three."]) + , ("Term2", [ para "This is a second definition"]) + ]) + , "One-line nested definition list" =: + " Foo :: bar :: baz" =?> + definitionList [ ("Foo", [ definitionList [ ("bar", [ para "baz" ])]])] + , "Nested definition list" =: + T.unlines + [ " First :: Second :: Third" + , " Fourth :: Fifth :: Sixth" + , " Seventh :: Eighth" + ] =?> + definitionList [ ("First", [ definitionList [ ("Second", [ para "Third" ]), + ("Fourth", [ definitionList [ ("Fifth", [ para "Sixth"] ) ] ] ) ] ] ) + , ("Seventh", [ para "Eighth" ]) + ] + , testGroup "Definition lists with multiple descriptions" + [ "Correctly indented second description" =: + T.unlines + [ " First term :: first description" + , " :: second description" + ] =?> + definitionList [ ("First term", [ para "first description" + , para "second description" + ]) + ] + , "Incorrectly indented second description" =: + T.unlines + [ " First term :: first description" + , " :: second description" + ] =?> + definitionList [ ("First term", [ para "first description" ]) + , ("", [ para "second description" ]) + ] + ] + , "Two blank lines separate definition lists" =: + T.unlines + [ " First :: list" + , "" + , "" + , " Second :: list" + ] =?> + definitionList [ ("First", [ para "list" ]) ] <> + definitionList [ ("Second", [ para "list" ]) ] + -- Headers in first column of list continuation are not allowed + , "No headers in list continuation" =: + T.unlines + [ " - Foo" + , "" + , " * Bar" + ] =?> + bulletList [ mconcat [ para "Foo" + , para "* Bar" + ] + ] + , "Bullet list inside a tag" =: + T.unlines + [ "" + , " - First" + , "" + , " - Second" + , "" + , " - Third" + , "" + ] =?> + blockQuote (bulletList [ para "First" + , para "Second" + , para "Third" + ]) + , "Ordered list inside a tag" =: + T.unlines + [ "" + , " 1. First" + , "" + , " 2. Second" + , "" + , " 3. Third" + , "" + ] =?> + blockQuote (orderedListWith (1, Decimal, Period) [ para "First" + , para "Second" + , para "Third" + ]) + -- Regression test for a bug caught by round-trip test + , "Do not consume whitespace while looking for end tag" =: + T.unlines + [ "" + , " - " + , " foo" + , " " + , " bar" -- Do not consume whitespace while looking for arbitraritly indented + , "" + ] =?> + blockQuote (bulletList [ blockQuote $ para "foo" ] <> para "bar") + + , "Unclosed quote tag" =: + T.unlines + [ "" + , "" + , "" + , "" + ] =?> + para "" <> lineBlock [ "" ] + + , "Unclosed quote tag inside list" =: + T.unlines + [ " - " + , " " + , " " + , " " + ] =?> + bulletList [ para "" <> lineBlock [ "" ] ] + + -- Allowing indented closing tags is dangerous, + -- as they may terminate lists + , "No indented closing tags" =: + T.unlines + [ "" + , "" + , " - Foo" + , "" + , " " + , "" + , " bar" + , "" + , " " + , " " + , " " + ] =?> + para "" <> bulletList [ para "Foo" <> para "" <> para "bar" <> lineBlock [ "" ] ] + ] + ] diff --git a/test/Tests/Readers/Odt.hs.orig b/test/Tests/Readers/Odt.hs.orig new file mode 100644 index 000000000..4b7058cf9 --- /dev/null +++ b/test/Tests/Readers/Odt.hs.orig @@ -0,0 +1,170 @@ +module Tests.Readers.Odt (tests) where + +import Control.Monad (liftM) +import qualified Data.ByteString as BS +import qualified Data.ByteString.Lazy as B +import qualified Data.Map as M +import Data.Text (unpack) +import System.IO.Unsafe (unsafePerformIO) +import Test.Tasty +import Tests.Helpers +import Text.Pandoc +import qualified Text.Pandoc.UTF8 as UTF8 + +defopts :: ReaderOptions +defopts = def{ readerExtensions = getDefaultExtensions "odt" } + +tests :: [TestTree] +tests = testsComparingToMarkdown ++ testsComparingToNative + +testsComparingToMarkdown :: [TestTree] +testsComparingToMarkdown = map nameToTest namesOfTestsComparingToMarkdown + where nameToTest name = createTest + compareOdtToMarkdown + name + (toOdtPath name) + (toMarkdownPath name) + toOdtPath name = "odt/odt/" ++ name ++ ".odt" + toMarkdownPath name = "odt/markdown/" ++ name ++ ".md" + +testsComparingToNative :: [TestTree] +testsComparingToNative = map nameToTest namesOfTestsComparingToNative + where nameToTest name = createTest + compareOdtToNative + name + (toOdtPath name) + (toNativePath name) + toOdtPath name = "odt/odt/" ++ name ++ ".odt" + toNativePath name = "odt/native/" ++ name ++ ".native" + + +newtype NoNormPandoc = NoNormPandoc {unNoNorm :: Pandoc} + deriving ( Show ) + +instance ToString NoNormPandoc where + toString d = unpack $ + purely (writeNative def{ writerTemplate = s }) $ toPandoc d + where s = case d of + NoNormPandoc (Pandoc (Meta m) _) + | M.null m -> Nothing + | otherwise -> Just "" -- need this for Meta output + +instance ToPandoc NoNormPandoc where + toPandoc = unNoNorm + +getNoNormVia :: (a -> Pandoc) -> String -> Either PandocError a -> NoNormPandoc +getNoNormVia _ readerName (Left _) = error (readerName ++ " reader failed") +getNoNormVia f _ (Right a) = NoNormPandoc (f a) + +type TestCreator = ReaderOptions + -> FilePath -> FilePath + -> IO (NoNormPandoc, NoNormPandoc) + +compareOdtToNative :: TestCreator +compareOdtToNative opts odtPath nativePath = do + nativeFile <- UTF8.toText <$> BS.readFile nativePath + odtFile <- B.readFile odtPath + native <- getNoNormVia id "native" <$> runIO (readNative def nativeFile) + odt <- getNoNormVia id "odt" <$> runIO (readOdt opts odtFile) + return (odt,native) + +compareOdtToMarkdown :: TestCreator +compareOdtToMarkdown opts odtPath markdownPath = do + markdownFile <- UTF8.toText <$> BS.readFile markdownPath + odtFile <- B.readFile odtPath + markdown <- getNoNormVia id "markdown" <$> + runIO (readMarkdown def{ readerExtensions = pandocExtensions } + markdownFile) + odt <- getNoNormVia id "odt" <$> runIO (readOdt opts odtFile) + return (odt,markdown) + + +createTest :: TestCreator + -> TestName + -> FilePath -> FilePath + -> TestTree +createTest creator name path1 path2 = + unsafePerformIO $ liftM (test id name) (creator defopts path1 path2) + +{- +-- + +getMedia :: FilePath -> FilePath -> IO (Maybe B.ByteString) +getMedia archivePath mediaPath = do + zf <- B.readFile archivePath >>= return . toArchive + return $ findEntryByPath ("Pictures/" ++ mediaPath) zf >>= (Just . fromEntry) + +compareMediaPathIO :: FilePath -> MediaBag -> FilePath -> IO Bool +compareMediaPathIO mediaPath mediaBag odtPath = do + odtMedia <- getMedia odtPath mediaPath + let mbBS = case lookupMedia mediaPath mediaBag of + Just (_, bs) -> bs + Nothing -> error ("couldn't find " ++ + mediaPath ++ + " in media bag") + odtBS = case odtMedia of + Just bs -> bs + Nothing -> error ("couldn't find " ++ + mediaPath ++ + " in media bag") + return $ mbBS == odtBS + +compareMediaBagIO :: FilePath -> IO Bool +compareMediaBagIO odtFile = do + df <- B.readFile odtFile + let (_, mb) = readOdt def df + bools <- mapM + (\(fp, _, _) -> compareMediaPathIO fp mb odtFile) + (mediaDirectory mb) + return $ and bools + +testMediaBagIO :: String -> FilePath -> IO TestTree +testMediaBagIO name odtFile = do + outcome <- compareMediaBagIO odtFile + return $ testCase name (assertBool + ("Media didn't match media bag in file " ++ odtFile) + outcome) + +testMediaBag :: String -> FilePath -> TestTree +testMediaBag name odtFile = buildTest $ testMediaBagIO name odtFile +-} +-- + + + +namesOfTestsComparingToMarkdown :: [ String ] +namesOfTestsComparingToMarkdown = [ "bold" +-- , "citation" + , "endnote" + , "externalLink" + , "footnote" + , "headers" +-- , "horizontalRule" + , "italic" +-- , "listBlocks" + , "paragraph" + , "strikeout" +-- , "trackedChanges" + , "underlined" + ] + +namesOfTestsComparingToNative :: [ String ] +namesOfTestsComparingToNative = [ "blockquote" + , "image" + , "imageIndex" + , "imageWithCaption" + , "inlinedCode" + , "orderedListMixed" + , "orderedListRoman" + , "orderedListSimple" + , "referenceToChapter" + , "referenceToListItem" + , "referenceToText" + , "simpleTable" + , "simpleTableWithCaption" +-- , "table" + , "textMixedStyles" + , "tableWithContents" + , "unicode" + , "unorderedList" + ] diff --git a/test/Tests/Readers/Org.hs.orig b/test/Tests/Readers/Org.hs.orig new file mode 100644 index 000000000..de7f14e32 --- /dev/null +++ b/test/Tests/Readers/Org.hs.orig @@ -0,0 +1,16 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Readers.Org (tests) where + +import Test.Tasty (TestTree, testGroup) +import qualified Tests.Readers.Org.Block as Block +import qualified Tests.Readers.Org.Directive as Directive +import qualified Tests.Readers.Org.Inline as Inline +import qualified Tests.Readers.Org.Meta as Meta + +tests :: [TestTree] +tests = + [ testGroup "Inlines" Inline.tests + , testGroup "Basic Blocks" Block.tests + , testGroup "Meta Information" Meta.tests + , testGroup "Directives" Directive.tests + ] diff --git a/test/Tests/Readers/Org/Block.hs.orig b/test/Tests/Readers/Org/Block.hs.orig new file mode 100644 index 000000000..15dc63554 --- /dev/null +++ b/test/Tests/Readers/Org/Block.hs.orig @@ -0,0 +1,192 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Readers.Org.Block (tests) where + +import Test.Tasty (TestTree, testGroup) +import Tests.Helpers ((=?>)) +import Tests.Readers.Org.Shared ((=:), spcSep) +import Text.Pandoc.Builder +import qualified Data.Text as T +import qualified Tests.Readers.Org.Block.CodeBlock as CodeBlock +import qualified Tests.Readers.Org.Block.Figure as Figure +import qualified Tests.Readers.Org.Block.Header as Header +import qualified Tests.Readers.Org.Block.List as List +import qualified Tests.Readers.Org.Block.Table as Table + +tests :: [TestTree] +tests = + [ "Paragraph" =: + "Paragraph\n" =?> + para "Paragraph" + + , "Paragraph starting with an asterisk" =: + "*five" =?> + para "*five" + + , "Paragraph containing asterisk at beginning of line" =: + T.unlines [ "lucky" + , "*star" + ] =?> + para ("lucky" <> softbreak <> "*star") + + , "Example block" =: + T.unlines [ ": echo hello" + , ": echo dear tester" + ] =?> + codeBlockWith ("", ["example"], []) "echo hello\necho dear tester\n" + + , "Example block surrounded by text" =: + T.unlines [ "Greetings" + , ": echo hello" + , ": echo dear tester" + , "Bye" + ] =?> + mconcat [ para "Greetings" + , codeBlockWith ("", ["example"], []) + "echo hello\necho dear tester\n" + , para "Bye" + ] + + , "Horizontal Rule" =: + T.unlines [ "before" + , "-----" + , "after" + ] =?> + mconcat [ para "before" + , horizontalRule + , para "after" + ] + + , "Not a Horizontal Rule" =: + "----- em and en dash" =?> + para "\8212\8211 em and en dash" + + , "Comment Block" =: + T.unlines [ "#+BEGIN_COMMENT" + , "stuff" + , "bla" + , "#+END_COMMENT"] =?> + (mempty::Blocks) + + , testGroup "Blocks and fragments" + [ "HTML block" =: + T.unlines [ "#+BEGIN_HTML" + , "" + , "#+END_HTML" + ] =?> + rawBlock "html" "\n" + + , "Quote block" =: + T.unlines [ "#+BEGIN_QUOTE" + , "/Niemand/ hat die Absicht, eine Mauer zu errichten!" + , "#+END_QUOTE" + ] =?> + blockQuote (para (spcSep [ emph "Niemand", "hat", "die", "Absicht," + , "eine", "Mauer", "zu", "errichten!" + ])) + + , "Verse block" =: + T.unlines [ "The first lines of Goethe's /Faust/:" + , "#+begin_verse" + , "Habe nun, ach! Philosophie," + , "Juristerei und Medizin," + , "Und leider auch Theologie!" + , "Durchaus studiert, mit heißem Bemühn." + , "#+end_verse" + ] =?> + mconcat + [ para $ spcSep [ "The", "first", "lines", "of" + , "Goethe's", emph "Faust" <> ":"] + , lineBlock + [ "Habe nun, ach! Philosophie," + , "Juristerei und Medizin," + , "Und leider auch Theologie!" + , "Durchaus studiert, mit heißem Bemühn." + ] + ] + + , "Verse block with blank lines" =: + T.unlines [ "#+BEGIN_VERSE" + , "foo" + , "" + , "bar" + , "#+END_VERSE" + ] =?> + lineBlock [ "foo", mempty, "bar" ] + + , "Verse block with varying indentation" =: + T.unlines [ "#+BEGIN_VERSE" + , " hello darkness" + , "my old friend" + , "#+END_VERSE" + ] =?> + lineBlock [ "\160\160hello darkness", "my old friend" ] + + , "Raw block LaTeX" =: + T.unlines [ "#+BEGIN_LaTeX" + , "The category $\\cat{Set}$ is adhesive." + , "#+END_LaTeX" + ] =?> + rawBlock "latex" "The category $\\cat{Set}$ is adhesive.\n" + + , "Raw LaTeX line" =: + "#+LATEX: \\let\\foo\\bar" =?> + rawBlock "latex" "\\let\\foo\\bar" + + , "Raw Beamer line" =: + "#+beamer: \\pause" =?> + rawBlock "beamer" "\\pause" + + , "Raw HTML line" =: + "#+HTML: " =?> + rawBlock "html" "" + + , "Export block HTML" =: + T.unlines [ "#+BEGIN_export html" + , "Hello, World!" + , "#+END_export" + ] =?> + rawBlock "html" "Hello, World!\n" + + , "LaTeX fragment" =: + T.unlines [ "\\begin{equation}" + , "X_i = \\begin{cases}" + , " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) = \\alpha(i)\\\\" + , " C_{\\alpha(i)} & \\text{otherwise}" + , " \\end{cases}" + , "\\end{equation}" + ] =?> + rawBlock "latex" + (unlines [ "\\begin{equation}" + , "X_i = \\begin{cases}" + , " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) =" <> + " \\alpha(i)\\\\" + , " C_{\\alpha(i)} & \\text{otherwise}" + , " \\end{cases}" + , "\\end{equation}" + ]) + + , "Convert blank lines in blocks to single newlines" =: + T.unlines [ "#+begin_html" + , "" + , "boring" + , "" + , "#+end_html" + ] =?> + rawBlock "html" "\nboring\n\n" + + , "Accept `ATTR_HTML` attributes for generic block" =: + T.unlines [ "#+ATTR_HTML: :title hello, world :id test :class fun code" + , "#+BEGIN_TEST" + , "nonsense" + , "#+END_TEST" + ] =?> + let attr = ("test", ["fun", "code", "TEST"], [("title", "hello, world")]) + in divWith attr (para "nonsense") + ] + + , testGroup "Headers" Header.tests + , testGroup "Figures" Figure.tests + , testGroup "Lists" List.tests + , testGroup "CodeBlocks" CodeBlock.tests + , testGroup "Tables" Table.tests + ] diff --git a/test/Tests/Readers/Org/Block/CodeBlock.hs.orig b/test/Tests/Readers/Org/Block/CodeBlock.hs.orig new file mode 100644 index 000000000..8fa822089 --- /dev/null +++ b/test/Tests/Readers/Org/Block/CodeBlock.hs.orig @@ -0,0 +1,194 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Readers.Org.Block.CodeBlock (tests) where + +import Test.Tasty (TestTree) +import Tests.Helpers ((=?>)) +import Tests.Readers.Org.Shared ((=:), spcSep) +import Text.Pandoc.Builder +import qualified Data.Text as T + +tests :: [TestTree] +tests = + [ "Source block" =: + T.unlines [ " #+BEGIN_SRC haskell" + , " main = putStrLn greeting" + , " where greeting = \"moin\"" + , " #+END_SRC" ] =?> + let attr' = ("", ["haskell"], []) + code' = "main = putStrLn greeting\n" <> + " where greeting = \"moin\"\n" + in codeBlockWith attr' code' + + , "Source block with indented code" =: + T.unlines [ " #+BEGIN_SRC haskell" + , " main = putStrLn greeting" + , " where greeting = \"moin\"" + , " #+END_SRC" ] =?> + let attr' = ("", ["haskell"], []) + code' = "main = putStrLn greeting\n" <> + " where greeting = \"moin\"\n" + in codeBlockWith attr' code' + + , "Source block with tab-indented code" =: + T.unlines [ "\t#+BEGIN_SRC haskell" + , "\tmain = putStrLn greeting" + , "\t where greeting = \"moin\"" + , "\t#+END_SRC" ] =?> + let attr' = ("", ["haskell"], []) + code' = "main = putStrLn greeting\n" <> + " where greeting = \"moin\"\n" + in codeBlockWith attr' code' + + , "Empty source block" =: + T.unlines [ " #+BEGIN_SRC haskell" + , " #+END_SRC" ] =?> + let attr' = ("", ["haskell"], []) + code' = "" + in codeBlockWith attr' code' + + , "Source block between paragraphs" =: + T.unlines [ "Low German greeting" + , " #+BEGIN_SRC haskell" + , " main = putStrLn greeting" + , " where greeting = \"Moin!\"" + , " #+END_SRC" ] =?> + let attr' = ("", ["haskell"], []) + code' = "main = putStrLn greeting\n" <> + " where greeting = \"Moin!\"\n" + in mconcat [ para $ spcSep [ "Low", "German", "greeting" ] + , codeBlockWith attr' code' + ] + , "Source block with babel arguments" =: + T.unlines [ "#+BEGIN_SRC emacs-lisp :exports both" + , "(progn (message \"Hello, World!\")" + , " (+ 23 42))" + , "#+END_SRC" ] =?> + let classes = [ "commonlisp" ] -- as kate doesn't know emacs-lisp syntax + params = [ ("org-language", "emacs-lisp") + , ("exports", "both") + ] + code' = unlines [ "(progn (message \"Hello, World!\")" + , " (+ 23 42))" ] + in codeBlockWith ("", classes, params) code' + + , "Source block with results and :exports both" =: + T.unlines [ "#+BEGIN_SRC emacs-lisp :exports both" + , "(progn (message \"Hello, World!\")" + , " (+ 23 42))" + , "#+END_SRC" + , "" + , "#+RESULTS:" + , ": 65"] =?> + let classes = [ "commonlisp" ] + params = [ ("org-language", "emacs-lisp") + , ("exports", "both") + ] + code' = unlines [ "(progn (message \"Hello, World!\")" + , " (+ 23 42))" ] + results' = "65\n" + in codeBlockWith ("", classes, params) code' + <> + codeBlockWith ("", ["example"], []) results' + + , "Source block with results and :exports code" =: + T.unlines [ "#+BEGIN_SRC emacs-lisp :exports code" + , "(progn (message \"Hello, World!\")" + , " (+ 23 42))" + , "#+END_SRC" + , "" + , "#+RESULTS:" + , ": 65" ] =?> + let classes = [ "commonlisp" ] + params = [ ("org-language", "emacs-lisp") + , ("exports", "code") + ] + code' = unlines [ "(progn (message \"Hello, World!\")" + , " (+ 23 42))" ] + in codeBlockWith ("", classes, params) code' + + , "Source block with results and :exports results" =: + T.unlines [ "#+BEGIN_SRC emacs-lisp :exports results" + , "(progn (message \"Hello, World!\")" + , " (+ 23 42))" + , "#+END_SRC" + , "" + , "#+RESULTS:" + , ": 65" ] =?> + let results' = "65\n" + in codeBlockWith ("", ["example"], []) results' + + , "Source block with results and :exports none" =: + T.unlines [ "#+BEGIN_SRC emacs-lisp :exports none" + , "(progn (message \"Hello, World!\")" + , " (+ 23 42))" + , "#+END_SRC" + , "" + , "#+RESULTS:" + , ": 65" ] =?> + (mempty :: Blocks) + + , "Source block with toggling header arguments" =: + T.unlines [ "#+BEGIN_SRC sh :noeval" + , "echo $HOME" + , "#+END_SRC" + ] =?> + let classes = [ "bash" ] + params = [ ("org-language", "sh"), ("noeval", "yes") ] + in codeBlockWith ("", classes, params) "echo $HOME\n" + + , "Source block with line number switch" =: + T.unlines [ "#+BEGIN_SRC sh -n 10" + , ":() { :|:& };:" + , "#+END_SRC" + ] =?> + let classes = [ "bash", "numberLines" ] + params = [ ("org-language", "sh"), ("startFrom", "10") ] + in codeBlockWith ("", classes, params) ":() { :|:& };:\n" + + , "Source block with multi-word parameter values" =: + T.unlines [ "#+BEGIN_SRC dot :cmdline -Kdot -Tpng " + , "digraph { id [label=\"ID\"] }" + , "#+END_SRC" + ] =?> + let classes = [ "dot" ] + params = [ ("cmdline", "-Kdot -Tpng") ] + in codeBlockWith ("", classes, params) "digraph { id [label=\"ID\"] }\n" + + , "Example block" =: + T.unlines [ "#+begin_example" + , "A chosen representation of" + , "a rule." + , "#+eND_exAMPle" + ] =?> + codeBlockWith ("", ["example"], []) + "A chosen representation of\na rule.\n" + + , "Code block with caption" =: + T.unlines [ "#+CAPTION: Functor laws in Haskell" + , "#+NAME: functor-laws" + , "#+BEGIN_SRC haskell" + , "fmap id = id" + , "fmap (p . q) = (fmap p) . (fmap q)" + , "#+END_SRC" + ] =?> + divWith + nullAttr + (mappend + (plain $ spanWith ("", ["label"], []) + (spcSep [ "Functor", "laws", "in", "Haskell" ])) + (codeBlockWith ("functor-laws", ["haskell"], []) + (unlines [ "fmap id = id" + , "fmap (p . q) = (fmap p) . (fmap q)" + ]))) + + , "Non-letter chars in source block parameters" =: + T.unlines [ "#+BEGIN_SRC C :tangle xxxx.c :city Zürich" + , "code body" + , "#+END_SRC" + ] =?> + let params = [ ("org-language", "C") + , ("tangle", "xxxx.c") + , ("city", "Zürich") + ] + in codeBlockWith ( "", ["c"], params) "code body\n" + ] diff --git a/test/Tests/Readers/Org/Block/Figure.hs.orig b/test/Tests/Readers/Org/Block/Figure.hs.orig new file mode 100644 index 000000000..cae6ef179 --- /dev/null +++ b/test/Tests/Readers/Org/Block/Figure.hs.orig @@ -0,0 +1,57 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Readers.Org.Block.Figure (tests) where + +import Test.Tasty (TestTree) +import Tests.Helpers ((=?>)) +import Tests.Readers.Org.Shared ((=:)) +import Text.Pandoc.Builder (image, imageWith, para) +import qualified Data.Text as T + +tests :: [TestTree] +tests = + [ "Figure" =: + T.unlines [ "#+caption: A very courageous man." + , "#+name: goodguy" + , "[[file:edward.jpg]]" + ] =?> + para (image "edward.jpg" "fig:goodguy" "A very courageous man.") + + , "Figure with no name" =: + T.unlines [ "#+caption: I've been through the desert on this" + , "[[file:horse.png]]" + ] =?> + para (image "horse.png" "fig:" "I've been through the desert on this") + + , "Figure with `fig:` prefix in name" =: + T.unlines [ "#+caption: Used as a metapher in evolutionary biology." + , "#+name: fig:redqueen" + , "[[./the-red-queen.jpg]]" + ] =?> + para (image "./the-red-queen.jpg" "fig:redqueen" + "Used as a metapher in evolutionary biology.") + + , "Figure with HTML attributes" =: + T.unlines [ "#+CAPTION: mah brain just explodid" + , "#+NAME: lambdacat" + , "#+ATTR_HTML: :style color: blue :role button" + , "[[file:lambdacat.jpg]]" + ] =?> + let kv = [("style", "color: blue"), ("role", "button")] + name = "fig:lambdacat" + caption = "mah brain just explodid" + in para (imageWith (mempty, mempty, kv) "lambdacat.jpg" name caption) + + , "Labelled figure" =: + T.unlines [ "#+CAPTION: My figure" + , "#+LABEL: fig:myfig" + , "[[file:blub.png]]" + ] =?> + let attr = ("fig:myfig", mempty, mempty) + in para (imageWith attr "blub.png" "fig:" "My figure") + + , "Figure with empty caption" =: + T.unlines [ "#+CAPTION:" + , "[[file:guess.jpg]]" + ] =?> + para (image "guess.jpg" "fig:" "") + ] diff --git a/test/Tests/Readers/Org/Block/Header.hs.orig b/test/Tests/Readers/Org/Block/Header.hs.orig new file mode 100644 index 000000000..e8ad88558 --- /dev/null +++ b/test/Tests/Readers/Org/Block/Header.hs.orig @@ -0,0 +1,182 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Readers.Org.Block.Header (tests) where + +import Test.Tasty (TestTree, testGroup) +import Tests.Helpers ((=?>)) +import Tests.Readers.Org.Shared ((=:), spcSep, tagSpan) +import Text.Pandoc.Builder +import qualified Data.Text as T + +tests :: [TestTree] +tests = + [ "First Level Header" =: + "* Headline\n" =?> + headerWith ("headline", [], []) 1 "Headline" + + , "Third Level Header" =: + "*** Third Level Headline\n" =?> + headerWith ("third-level-headline", [], []) + 3 + ("Third" <> space <> "Level" <> space <> "Headline") + + , "Compact Headers with Paragraph" =: + T.unlines [ "* First Level" + , "** Second Level" + , " Text" + ] =?> + mconcat [ headerWith ("first-level", [], []) + 1 + ("First" <> space <> "Level") + , headerWith ("second-level", [], []) + 2 + ("Second" <> space <> "Level") + , para "Text" + ] + + , "Separated Headers with Paragraph" =: + T.unlines [ "* First Level" + , "" + , "** Second Level" + , "" + , " Text" + ] =?> + mconcat [ headerWith ("first-level", [], []) + 1 + ("First" <> space <> "Level") + , headerWith ("second-level", [], []) + 2 + ("Second" <> space <> "Level") + , para "Text" + ] + + , "Headers not preceded by a blank line" =: + T.unlines [ "** eat dinner" + , "Spaghetti and meatballs tonight." + , "** walk dog" + ] =?> + mconcat [ headerWith ("eat-dinner", [], []) + 2 + ("eat" <> space <> "dinner") + , para $ spcSep [ "Spaghetti", "and", "meatballs", "tonight." ] + , headerWith ("walk-dog", [], []) + 2 + ("walk" <> space <> "dog") + ] + + , testGroup "Todo keywords" + [ "Header with known todo keyword" =: + "* TODO header" =?> + let todoSpan = spanWith ("", ["todo", "TODO"], []) "TODO" + in headerWith ("header", [], []) 1 (todoSpan <> space <> "header") + + , "Header marked as done" =: + "* DONE header" =?> + let todoSpan = spanWith ("", ["done", "DONE"], []) "DONE" + in headerWith ("header", [], []) 1 (todoSpan <> space <> "header") + + , "Header with unknown todo keyword" =: + "* WAITING header" =?> + headerWith ("waiting-header", [], []) 1 "WAITING header" + + , "Custom todo keywords" =: + T.unlines [ "#+TODO: WAITING CANCELLED" + , "* WAITING compile" + , "* CANCELLED lunch" + ] =?> + let todoSpan = spanWith ("", ["todo", "WAITING"], []) "WAITING" + doneSpan = spanWith ("", ["done", "CANCELLED"], []) "CANCELLED" + in headerWith ("compile", [], []) 1 (todoSpan <> space <> "compile") + <> headerWith ("lunch", [], []) 1 (doneSpan <> space <> "lunch") + + , "Custom todo keywords with multiple done-states" =: + T.unlines [ "#+TODO: WAITING | DONE CANCELLED " + , "* WAITING compile" + , "* CANCELLED lunch" + , "* DONE todo-feature" + ] =?> + let waiting = spanWith ("", ["todo", "WAITING"], []) "WAITING" + cancelled = spanWith ("", ["done", "CANCELLED"], []) "CANCELLED" + done = spanWith ("", ["done", "DONE"], []) "DONE" + in headerWith ("compile", [], []) 1 (waiting <> space <> "compile") + <> headerWith ("lunch", [], []) 1 (cancelled <> space <> "lunch") + <> headerWith ("todo-feature", [], []) 1 (done <> space <> "todo-feature") + ] + + , "Tagged headers" =: + T.unlines [ "* Personal :PERSONAL:" + , "** Call Mom :@PHONE:" + , "** Call John :@PHONE:JOHN: " + ] =?> + mconcat [ headerWith ("personal", [], []) + 1 + ("Personal " <> tagSpan "PERSONAL") + , headerWith ("call-mom", [], []) + 2 + ("Call Mom " <> tagSpan "@PHONE") + , headerWith ("call-john", [], []) + 2 + ("Call John " <> tagSpan "@PHONE" <> "\160" <> tagSpan "JOHN") + ] + + , "Untagged header containing colons" =: + "* This: is not: tagged" =?> + headerWith ("this-is-not-tagged", [], []) 1 "This: is not: tagged" + + , "Header starting with strokeout text" =: + T.unlines [ "foo" + , "" + , "* +thing+ other thing" + ] =?> + mconcat [ para "foo" + , headerWith ("thing-other-thing", [], []) + 1 + (strikeout "thing" <> " other thing") + ] + + , "Comment Trees" =: + T.unlines [ "* COMMENT A comment tree" + , " Not much going on here" + , "** This will be dropped" + , "* Comment tree above" + ] =?> + headerWith ("comment-tree-above", [], []) 1 "Comment tree above" + + , "Nothing but a COMMENT header" =: + "* COMMENT Test" =?> + (mempty::Blocks) + + , "Tree with :noexport:" =: + T.unlines [ "* Should be ignored :archive:noexport:old:" + , "** Old stuff" + , " This is not going to be exported" + ] =?> + (mempty::Blocks) + + , "Subtree with :noexport:" =: + T.unlines [ "* Exported" + , "** This isn't exported :noexport:" + , "*** This neither" + , "** But this is" + ] =?> + mconcat [ headerWith ("exported", [], []) 1 "Exported" + , headerWith ("but-this-is", [], []) 2 "But this is" + ] + + , "Preferences are treated as header attributes" =: + T.unlines [ "* foo" + , " :PROPERTIES:" + , " :custom_id: fubar" + , " :bar: baz" + , " :END:" + ] =?> + headerWith ("fubar", [], [("bar", "baz")]) 1 "foo" + + + , "Headers marked with a unnumbered property get a class of the same name" =: + T.unlines [ "* Not numbered" + , " :PROPERTIES:" + , " :UNNUMBERED: t" + , " :END:" + ] =?> + headerWith ("not-numbered", ["unnumbered"], []) 1 "Not numbered" + ] diff --git a/test/Tests/Readers/Org/Block/List.hs.orig b/test/Tests/Readers/Org/Block/List.hs.orig new file mode 100644 index 000000000..343682a80 --- /dev/null +++ b/test/Tests/Readers/Org/Block/List.hs.orig @@ -0,0 +1,244 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Readers.Org.Block.List (tests) where + +import Test.Tasty (TestTree) +import Tests.Helpers ((=?>)) +import Tests.Readers.Org.Shared ((=:), spcSep) +import Text.Pandoc.Builder +import qualified Data.Text as T + +tests :: [TestTree] +tests = + [ "Simple Bullet Lists" =: + ("- Item1\n" <> + "- Item2\n") =?> + bulletList [ plain "Item1" + , plain "Item2" + ] + + , "Indented Bullet Lists" =: + (" - Item1\n" <> + " - Item2\n") =?> + bulletList [ plain "Item1" + , plain "Item2" + ] + + , "Unindented *" =: + ("- Item1\n" <> + "* Item2\n") =?> + bulletList [ plain "Item1" + ] <> + headerWith ("item2", [], []) 1 "Item2" + + , "Multi-line Bullet Lists" =: + ("- *Fat\n" <> + " Tony*\n" <> + "- /Sideshow\n" <> + " Bob/") =?> + bulletList [ plain $ strong ("Fat" <> softbreak <> "Tony") + , plain $ emph ("Sideshow" <> softbreak <> "Bob") + ] + + , "Nested Bullet Lists" =: + ("- Discovery\n" <> + " + One More Time\n" <> + " + Harder, Better, Faster, Stronger\n" <> + "- Homework\n" <> + " + Around the World\n"<> + "- Human After All\n" <> + " + Technologic\n" <> + " + Robot Rock\n") =?> + bulletList [ mconcat + [ plain "Discovery" + , bulletList [ plain ("One" <> space <> + "More" <> space <> + "Time") + , plain ("Harder," <> space <> + "Better," <> space <> + "Faster," <> space <> + "Stronger") + ] + ] + , mconcat + [ plain "Homework" + , bulletList [ plain ("Around" <> space <> + "the" <> space <> + "World") + ] + ] + , mconcat + [ plain ("Human" <> space <> "After" <> space <> "All") + , bulletList [ plain "Technologic" + , plain ("Robot" <> space <> "Rock") + ] + ] + ] + + , "Bullet List with Decreasing Indent" =: + " - Discovery\n\ + \ - Human After All\n" =?> + mconcat [ bulletList [ plain "Discovery" ] + , bulletList [ plain ("Human" <> space <> "After" <> space <> "All")] + ] + + , "Header follows Bullet List" =: + " - Discovery\n\ + \ - Human After All\n\ + \* Homework" =?> + mconcat [ bulletList [ plain "Discovery" + , plain ("Human" <> space <> "After" <> space <> "All") + ] + , headerWith ("homework", [], []) 1 "Homework" + ] + + , "Bullet List Unindented with trailing Header" =: + "- Discovery\n\ + \- Homework\n\ + \* NotValidListItem" =?> + mconcat [ bulletList [ plain "Discovery" + , plain "Homework" + ] + , headerWith ("notvalidlistitem", [], []) 1 "NotValidListItem" + ] + + , "Empty bullet points" =: + T.unlines [ "-" + , "- " + ] =?> + bulletList [ plain "", plain "" ] + + , "Simple Ordered List" =: + ("1. Item1\n" <> + "2. Item2\n") =?> + let listStyle = (1, DefaultStyle, DefaultDelim) + listStructure = [ plain "Item1" + , plain "Item2" + ] + in orderedListWith listStyle listStructure + + , "Simple Ordered List with Parens" =: + ("1) Item1\n" <> + "2) Item2\n") =?> + let listStyle = (1, DefaultStyle, DefaultDelim) + listStructure = [ plain "Item1" + , plain "Item2" + ] + in orderedListWith listStyle listStructure + + , "Indented Ordered List" =: + (" 1. Item1\n" <> + " 2. Item2\n") =?> + let listStyle = (1, DefaultStyle, DefaultDelim) + listStructure = [ plain "Item1" + , plain "Item2" + ] + in orderedListWith listStyle listStructure + + , "Empty ordered list item" =: + T.unlines [ "1." + , "3. " + ] =?> + orderedList [ plain "", plain "" ] + + , "Nested Ordered Lists" =: + ("1. One\n" <> + " 1. One-One\n" <> + " 2. One-Two\n" <> + "2. Two\n" <> + " 1. Two-One\n"<> + " 2. Two-Two\n") =?> + let listStyle = (1, DefaultStyle, DefaultDelim) + listStructure = [ mconcat + [ plain "One" + , orderedList [ plain "One-One" + , plain "One-Two" + ] + ] + , mconcat + [ plain "Two" + , orderedList [ plain "Two-One" + , plain "Two-Two" + ] + ] + ] + in orderedListWith listStyle listStructure + + , "Ordered List in Bullet List" =: + ("- Emacs\n" <> + " 1. Org\n") =?> + bulletList [ plain "Emacs" <> + orderedList [ plain "Org"] + ] + + , "Bullet List in Ordered List" =: + ("1. GNU\n" <> + " - Freedom\n") =?> + orderedList [ plain "GNU" <> bulletList [ plain "Freedom" ] ] + + , "Definition List" =: + T.unlines [ "- PLL :: phase-locked loop" + , "- TTL ::" + , " transistor-transistor logic" + , "- PSK :: phase-shift keying" + , "" + , " a digital modulation scheme" + ] =?> + definitionList [ ("PLL", [ plain $ "phase-locked" <> space <> "loop" ]) + , ("TTL", [ plain $ "transistor-transistor" <> space <> + "logic" ]) + , ("PSK", [ mconcat + [ para $ "phase-shift" <> space <> "keying" + , para $ spcSep [ "a", "digital" + , "modulation", "scheme" ] + ] + ]) + ] + , "Definition list with multi-word term" =: + " - Elijah Wood :: He plays Frodo" =?> + definitionList [ ("Elijah" <> space <> "Wood", [plain $ "He" <> space <> "plays" <> space <> "Frodo"])] + , "Compact definition list" =: + T.unlines [ "- ATP :: adenosine 5' triphosphate" + , "- DNA :: deoxyribonucleic acid" + , "- PCR :: polymerase chain reaction" + , "" + ] =?> + definitionList + [ ("ATP", [ plain $ spcSep [ "adenosine", "5'", "triphosphate" ] ]) + , ("DNA", [ plain $ spcSep [ "deoxyribonucleic", "acid" ] ]) + , ("PCR", [ plain $ spcSep [ "polymerase", "chain", "reaction" ] ]) + ] + + , "Definition List With Trailing Header" =: + "- definition :: list\n\ + \- cool :: defs\n\ + \* header" =?> + mconcat [ definitionList [ ("definition", [plain "list"]) + , ("cool", [plain "defs"]) + ] + , headerWith ("header", [], []) 1 "header" + ] + + , "Definition lists double-colon markers must be surrounded by whitespace" =: + "- std::cout" =?> + bulletList [ plain "std::cout" ] + + , "Loose bullet list" =: + T.unlines [ "- apple" + , "" + , "- orange" + , "" + , "- peach" + ] =?> + bulletList [ para "apple" + , para "orange" + , para "peach" + ] + + , "Recognize preceding paragraphs in non-list contexts" =: + T.unlines [ "CLOSED: [2015-10-19 Mon 15:03]" + , "- Note taken on [2015-10-19 Mon 13:24]" + ] =?> + mconcat [ para "CLOSED: [2015-10-19 Mon 15:03]" + , bulletList [ plain "Note taken on [2015-10-19 Mon 13:24]" ] + ] + ] diff --git a/test/Tests/Readers/Org/Block/Table.hs.orig b/test/Tests/Readers/Org/Block/Table.hs.orig new file mode 100644 index 000000000..db6e756f8 --- /dev/null +++ b/test/Tests/Readers/Org/Block/Table.hs.orig @@ -0,0 +1,150 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Readers.Org.Block.Table (tests) where + +import Test.Tasty (TestTree) +import Tests.Helpers ((=?>)) +import Tests.Readers.Org.Shared ((=:), spcSep) +import Text.Pandoc.Builder +import qualified Data.Text as T + +simpleTable' :: Int + -> [Blocks] + -> [[Blocks]] + -> Blocks +simpleTable' n = table "" (replicate n (AlignDefault, 0.0)) + +tests :: [TestTree] +tests = + [ "Single cell table" =: + "|Test|" =?> + simpleTable' 1 mempty [[plain "Test"]] + + , "Multi cell table" =: + "| One | Two |" =?> + simpleTable' 2 mempty [ [ plain "One", plain "Two" ] ] + + , "Multi line table" =: + T.unlines [ "| One |" + , "| Two |" + , "| Three |" + ] =?> + simpleTable' 1 mempty + [ [ plain "One" ] + , [ plain "Two" ] + , [ plain "Three" ] + ] + + , "Empty table" =: + "||" =?> + simpleTable' 1 mempty [[mempty]] + + , "Glider Table" =: + T.unlines [ "| 1 | 0 | 0 |" + , "| 0 | 1 | 1 |" + , "| 1 | 1 | 0 |" + ] =?> + simpleTable' 3 mempty + [ [ plain "1", plain "0", plain "0" ] + , [ plain "0", plain "1", plain "1" ] + , [ plain "1", plain "1", plain "0" ] + ] + + , "Table between Paragraphs" =: + T.unlines [ "Before" + , "| One | Two |" + , "After" + ] =?> + mconcat [ para "Before" + , simpleTable' 2 mempty [ [ plain "One", plain "Two" ] ] + , para "After" + ] + + , "Table with Header" =: + T.unlines [ "| Species | Status |" + , "|--------------+--------------|" + , "| cervisiae | domesticated |" + , "| paradoxus | wild |" + ] =?> + simpleTable [ plain "Species", plain "Status" ] + [ [ plain "cervisiae", plain "domesticated" ] + , [ plain "paradoxus", plain "wild" ] + ] + + , "Table with final hline" =: + T.unlines [ "| cervisiae | domesticated |" + , "| paradoxus | wild |" + , "|--------------+--------------|" + ] =?> + simpleTable' 2 mempty + [ [ plain "cervisiae", plain "domesticated" ] + , [ plain "paradoxus", plain "wild" ] + ] + + , "Table in a box" =: + T.unlines [ "|---------|---------|" + , "| static | Haskell |" + , "| dynamic | Lisp |" + , "|---------+---------|" + ] =?> + simpleTable' 2 mempty + [ [ plain "static", plain "Haskell" ] + , [ plain "dynamic", plain "Lisp" ] + ] + + , "Table with empty cells" =: + "|||c|" =?> + simpleTable' 3 mempty [[mempty, mempty, plain "c"]] + + , "Table with empty rows" =: + T.unlines [ "| first |" + , "| |" + , "| third |" + ] =?> + simpleTable' 1 mempty [[plain "first"], [mempty], [plain "third"]] + + , "Table with alignment row" =: + T.unlines [ "| Numbers | Text | More |" + , "| | | |" + , "| 1 | One | foo |" + , "| 2 | Two | bar |" + ] =?> + table "" (zip [AlignCenter, AlignRight, AlignDefault] [0, 0, 0]) + [] + [ [ plain "Numbers", plain "Text", plain "More" ] + , [ plain "1" , plain "One" , plain "foo" ] + , [ plain "2" , plain "Two" , plain "bar" ] + ] + + , "Pipe within text doesn't start a table" =: + "Ceci n'est pas une | pipe " =?> + para (spcSep [ "Ceci", "n'est", "pas", "une", "|", "pipe" ]) + + , "Missing pipe at end of row" =: + "|incomplete-but-valid" =?> + simpleTable' 1 mempty [ [ plain "incomplete-but-valid" ] ] + + , "Table with differing row lengths" =: + T.unlines [ "| Numbers | Text " + , "|-" + , "| | |" + , "| 1 | One | foo |" + , "| 2" + ] =?> + table "" (zip [AlignCenter, AlignRight] [0, 0]) + [ plain "Numbers", plain "Text" ] + [ [ plain "1" , plain "One" , plain "foo" ] + , [ plain "2" ] + ] + + , "Table with caption" =: + T.unlines [ "#+CAPTION: Hitchhiker's Multiplication Table" + , "| x | 6 |" + , "| 9 | 42 |" + ] =?> + table "Hitchhiker's Multiplication Table" + [(AlignDefault, 0), (AlignDefault, 0)] + [] + [ [ plain "x", plain "6" ] + , [ plain "9", plain "42" ] + ] + ] diff --git a/test/Tests/Readers/Org/Directive.hs.orig b/test/Tests/Readers/Org/Directive.hs.orig new file mode 100644 index 000000000..7e2c0fb8d --- /dev/null +++ b/test/Tests/Readers/Org/Directive.hs.orig @@ -0,0 +1,199 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Readers.Org.Directive (tests) where + +import Data.Time (UTCTime (UTCTime), secondsToDiffTime) +import Data.Time.Calendar (Day (ModifiedJulianDay)) +import Test.Tasty (TestTree, testGroup) +import Tests.Helpers ((=?>), ToString, purely, test) +import Tests.Readers.Org.Shared ((=:), tagSpan) +import Text.Pandoc +import Text.Pandoc.Builder +import qualified Data.ByteString as BS +import qualified Data.Text as T + +testWithFiles :: (ToString c) + => [(FilePath, BS.ByteString)] + -> String -- ^ name of test case + -> (T.Text, c) -- ^ (input, expected value) + -> TestTree +testWithFiles fileDefs = test (orgWithFiles fileDefs) + where +orgWithFiles :: [(FilePath, BS.ByteString)] -> T.Text -> Pandoc +orgWithFiles fileDefs input = + let readOrg' = readOrg def{ readerExtensions = getDefaultExtensions "org" } + in flip purely input $ \inp -> do + modifyPureState (\st -> st { stFiles = files fileDefs }) + readOrg' inp + + +files :: [(FilePath, BS.ByteString)] -> FileTree +files fileDefs = + let dummyTime = UTCTime (ModifiedJulianDay 125) (secondsToDiffTime 0) + in foldr (\(fp, bs) -> insertInFileTree fp (FileInfo dummyTime bs)) + mempty fileDefs + +tests :: [TestTree] +tests = + [ testGroup "export options" + [ "disable simple sub/superscript syntax" =: + T.unlines [ "#+OPTIONS: ^:nil" + , "a^b" + ] =?> + para "a^b" + + , "directly select drawers to be exported" =: + T.unlines [ "#+OPTIONS: d:(\"IMPORTANT\")" + , ":IMPORTANT:" + , "23" + , ":END:" + , ":BORING:" + , "very boring" + , ":END:" + ] =?> + divWith (mempty, ["IMPORTANT", "drawer"], mempty) (para "23") + + , "exclude drawers from being exported" =: + T.unlines [ "#+OPTIONS: d:(not \"BORING\")" + , ":IMPORTANT:" + , "5" + , ":END:" + , ":BORING:" + , "very boring" + , ":END:" + ] =?> + divWith (mempty, ["IMPORTANT", "drawer"], mempty) (para "5") + + , "don't include archive trees" =: + T.unlines [ "#+OPTIONS: arch:nil" + , "* old :ARCHIVE:" + ] =?> + (mempty ::Blocks) + + , "include complete archive trees" =: + T.unlines [ "#+OPTIONS: arch:t" + , "* old :ARCHIVE:" + , " boring" + ] =?> + mconcat [ headerWith ("old", [], mempty) 1 + ("old" <> space <> tagSpan "ARCHIVE") + , para "boring" + ] + + , "include archive tree header only" =: + T.unlines [ "#+OPTIONS: arch:headline" + , "* old :ARCHIVE:" + , " boring" + ] =?> + headerWith ("old", [], mempty) 1 ("old" <> space <> tagSpan "ARCHIVE") + + , "limit headline depth" =: + T.unlines [ "#+OPTIONS: H:2" + , "* top-level section" + , "** subsection" + , "*** list item 1" + , "*** list item 2" + ] =?> + mconcat [ headerWith ("top-level-section", [], []) 1 "top-level section" + , headerWith ("subsection", [], []) 2 "subsection" + , orderedList [ para "list item 1", para "list item 2" ] + ] + + , "turn all headlines into lists" =: + T.unlines [ "#+OPTIONS: H:0" + , "first block" + , "* top-level section 1" + , "** subsection" + , "* top-level section 2" + ] =?> + mconcat [ para "first block" + , orderedList + [ para "top-level section 1" <> + orderedList [ para "subsection" ] + , para "top-level section 2" ] + ] + + , "preserve linebreaks as hard breaks" =: + T.unlines [ "#+OPTIONS: \\n:t" + , "first" + , "second" + ] =?> + para ("first" <> linebreak <> "second") + + , "disable author export" =: + T.unlines [ "#+OPTIONS: author:nil" + , "#+AUTHOR: ShyGuy" + ] =?> + Pandoc nullMeta mempty + + , "disable creator export" =: + T.unlines [ "#+OPTIONS: creator:nil" + , "#+creator: The Architect" + ] =?> + Pandoc nullMeta mempty + + , "disable email export" =: + T.unlines [ "#+OPTIONS: email:nil" + , "#+email: no-mail-please@example.com" + ] =?> + Pandoc nullMeta mempty + + , "disable inclusion of todo keywords" =: + T.unlines [ "#+OPTIONS: todo:nil" + , "** DONE todo export" + ] =?> + headerWith ("todo-export", [], []) 2 "todo export" + + , "remove tags from headlines" =: + T.unlines [ "#+OPTIONS: tags:nil" + , "* Headline :hello:world:" + ] =?> + headerWith ("headline", [], mempty) 1 "Headline" + ] + + , testGroup "Include" + [ testWithFiles [("./other.org", "content of other file\n")] + "file inclusion" + (T.unlines [ "#+include: \"other.org\"" ] =?> + plain "content of other file") + + , testWithFiles [("./world.org", "World\n\n")] + "Included file belongs to item" + (T.unlines [ "- Hello,\n #+include: \"world.org\"" ] =?> + bulletList [para "Hello," <> para "World"]) + + , testWithFiles [("./level3.org", "*** Level3\n\n")] + "Default include preserves level" + (T.unlines [ "#+include: \"level3.org\"" ] =?> + headerWith ("level3", [], []) 3 "Level3") + + , testWithFiles [("./level3.org", "*** Level3\n\n")] + "Minlevel shifts level" + (T.unlines [ "#+include: \"level3.org\" :minlevel 1" ] =?> + headerWith ("level3", [], []) 1 "Level3") + + , testWithFiles [("./src.hs", "putStrLn outString\n")] + "Include file as source code snippet" + (T.unlines [ "#+include: \"src.hs\" src haskell" ] =?> + codeBlockWith ("", ["haskell"], []) "putStrLn outString\n") + + , testWithFiles [("./export-latex.org", "\\emph{Hello}\n")] + "Include file as export snippet" + (T.unlines [ "#+include: \"export-latex.org\" export latex" ] =?> + rawBlock "latex" "\\emph{Hello}\n") + + , testWithFiles [("./subdir/foo-bar.latex", "foo\n"), + ("./hello.lisp", "(print \"Hello!\")\n") + ] + "include directive is limited to one line" + (T.unlines [ "#+INCLUDE: \"hello.lisp\" src lisp" + , "#+include: \"subdir/foo-bar.latex\" export latex" + , "bar" + ] =?> + mconcat + [ codeBlockWith ("", ["lisp"], []) "(print \"Hello!\")\n" + , rawBlock "latex" "foo\n" + , para "bar" + ] + ) + ] + ] diff --git a/test/Tests/Readers/Org/Inline.hs.orig b/test/Tests/Readers/Org/Inline.hs.orig new file mode 100644 index 000000000..9bf5556d2 --- /dev/null +++ b/test/Tests/Readers/Org/Inline.hs.orig @@ -0,0 +1,352 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Readers.Org.Inline (tests) where + +import Data.List (intersperse) +import Test.Tasty (TestTree, testGroup) +import Tests.Helpers ((=?>)) +import Tests.Readers.Org.Shared ((=:), spcSep) +import Text.Pandoc.Builder +import Text.Pandoc.Shared (underlineSpan) +import qualified Data.Text as T +import qualified Tests.Readers.Org.Inline.Citation as Citation +import qualified Tests.Readers.Org.Inline.Note as Note +import qualified Tests.Readers.Org.Inline.Smart as Smart + +tests :: [TestTree] +tests = + [ "Plain String" =: + "Hello, World" =?> + para (spcSep [ "Hello,", "World" ]) + + , "Emphasis" =: + "/Planet Punk/" =?> + para (emph . spcSep $ ["Planet", "Punk"]) + + , "Strong" =: + "*Cider*" =?> + para (strong "Cider") + + , "Strong Emphasis" =: + "/*strength*/" =?> + para (emph . strong $ "strength") + + , "Emphasized Strong preceded by space" =: + " */super/*" =?> + para (strong . emph $ "super") + + , "Underline" =: + "_underline_" =?> + para (underlineSpan "underline") + + , "Strikeout" =: + "+Kill Bill+" =?> + para (strikeout . spcSep $ [ "Kill", "Bill" ]) + + , "Verbatim" =: + "=Robot.rock()=" =?> + para (code "Robot.rock()") + + , "Code" =: + "~word for word~" =?> + para (code "word for word") + + , "Math $..$" =: + "$E=mc^2$" =?> + para (math "E=mc^2") + + , "Math $$..$$" =: + "$$E=mc^2$$" =?> + para (displayMath "E=mc^2") + + , "Math \\[..\\]" =: + "\\[E=ℎν\\]" =?> + para (displayMath "E=ℎν") + + , "Math \\(..\\)" =: + "\\(σ_x σ_p ≥ \\frac{ℏ}{2}\\)" =?> + para (math "σ_x σ_p ≥ \\frac{ℏ}{2}") + + , "Symbol" =: + "A * symbol" =?> + para (str "A" <> space <> str "*" <> space <> "symbol") + + , "Superscript simple expression" =: + "2^-λ" =?> + para (str "2" <> superscript "-λ") + + , "Superscript multi char" =: + "2^{n-1}" =?> + para (str "2" <> superscript "n-1") + + , "Subscript simple expression" =: + "a_n" =?> + para (str "a" <> subscript "n") + + , "Subscript multi char" =: + "a_{n+1}" =?> + para (str "a" <> subscript "n+1") + + , "Linebreak" =: + "line \\\\ \nbreak" =?> + para ("line" <> linebreak <> "break") + + , "Inline note" =: + "[fn::Schreib mir eine E-Mail]" =?> + para (note $ para "Schreib mir eine E-Mail") + + , "Markup-chars not occuring on word break are symbols" =: + T.unlines [ "this+that+ +so+on" + , "seven*eight* nine*" + , "+not+funny+" + ] =?> + para ("this+that+ +so+on" <> softbreak <> + "seven*eight* nine*" <> softbreak <> + strikeout "not+funny") + + , "No empty markup" =: + "// ** __ <> == ~~ $$" =?> + para (spcSep [ "//", "**", "__", "<>", "==", "~~", "$$" ]) + + , "Adherence to Org's rules for markup borders" =: + "/t/& a/ / ./r/ (*l*) /e/! /b/." =?> + para (spcSep [ emph $ "t/&" <> space <> "a" + , "/" + , "./r/" + , "(" <> strong "l" <> ")" + , emph "e" <> "!" + , emph "b" <> "." + ]) + + , "Quotes are allowed border chars" =: + "/'yep/ *sure\"*" =?> + para (emph "'yep" <> space <> strong "sure\"") + + , "Spaces are forbidden border chars" =: + "/nada /" =?> + para "/nada /" + + , "Markup should work properly after a blank line" =: + T.unlines ["foo", "", "/bar/"] =?> + para (text "foo") <> + para (emph $ text "bar") + + , "Inline math must stay within three lines" =: + T.unlines [ "$a", "b", "c$", "$d", "e", "f", "g$" ] =?> + para (math "a\nb\nc" <> softbreak <> + "$d" <> softbreak <> "e" <> softbreak <> + "f" <> softbreak <> "g$") + + , "Single-character math" =: + "$a$ $b$! $c$?" =?> + para (spcSep [ math "a" + , "$b$!" + , math "c" <> "?" + ]) + + , "Markup may not span more than two lines" =: + "/this *is +totally\nnice+ not*\nemph/" =?> + para ("/this" <> space <> + strong ("is" <> space <> + strikeout ("totally" <> + softbreak <> "nice") <> + space <> "not") <> + softbreak <> "emph/") + + , "Sub- and superscript expressions" =: + T.unlines [ "a_(a(b)(c)d)" + , "e^(f(g)h)" + , "i_(jk)l)" + , "m^()n" + , "o_{p{q{}r}}" + , "s^{t{u}v}" + , "w_{xy}z}" + , "1^{}2" + , "3_{{}}" + , "4^(a(*b(c*)d))" + ] =?> + para (mconcat $ intersperse softbreak + [ "a" <> subscript "(a(b)(c)d)" + , "e" <> superscript "(f(g)h)" + , "i" <> subscript "(jk)" <> "l)" + , "m" <> superscript "()" <> "n" + , "o" <> subscript "p{q{}r}" + , "s" <> superscript "t{u}v" + , "w" <> subscript "xy" <> "z}" + , "1" <> superscript "" <> "2" + , "3" <> subscript "{}" + , "4" <> superscript ("(a(" <> strong "b(c" <> ")d))") + ]) + , "Verbatim text can contain equal signes (=)" =: + "=is_subst = True=" =?> + para (code "is_subst = True") + + , testGroup "Images" + [ "Image" =: + "[[./sunset.jpg]]" =?> + para (image "./sunset.jpg" "" "") + + , "Image with explicit file: prefix" =: + "[[file:sunrise.jpg]]" =?> + para (image "sunrise.jpg" "" "") + + , "Multiple images within a paragraph" =: + T.unlines [ "[[file:sunrise.jpg]]" + , "[[file:sunset.jpg]]" + ] =?> + para ((image "sunrise.jpg" "" "") + <> softbreak + <> (image "sunset.jpg" "" "")) + + , "Image with html attributes" =: + T.unlines [ "#+ATTR_HTML: :width 50%" + , "[[file:guinea-pig.gif]]" + ] =?> + para (imageWith ("", [], [("width", "50%")]) "guinea-pig.gif" "" "") + ] + + , "Explicit link" =: + "[[http://zeitlens.com/][pseudo-random /nonsense/]]" =?> + para (link "http://zeitlens.com/" "" + ("pseudo-random" <> space <> emph "nonsense")) + + , "Self-link" =: + "[[http://zeitlens.com/]]" =?> + para (link "http://zeitlens.com/" "" "http://zeitlens.com/") + + , "Absolute file link" =: + "[[/url][hi]]" =?> + para (link "file:///url" "" "hi") + + , "Link to file in parent directory" =: + "[[../file.txt][moin]]" =?> + para (link "../file.txt" "" "moin") + + , "Empty link (for gitit interop)" =: + "[[][New Link]]" =?> + para (link "" "" "New Link") + + , "Image link" =: + "[[sunset.png][file:dusk.svg]]" =?> + para (link "sunset.png" "" (image "dusk.svg" "" "")) + + , "Image link with non-image target" =: + "[[http://example.com][./logo.png]]" =?> + para (link "http://example.com" "" (image "./logo.png" "" "")) + + , "Plain link" =: + "Posts on http://zeitlens.com/ can be funny at times." =?> + para (spcSep [ "Posts", "on" + , link "http://zeitlens.com/" "" "http://zeitlens.com/" + , "can", "be", "funny", "at", "times." + ]) + + , "Angle link" =: + "Look at for fnords." =?> + para (spcSep [ "Look", "at" + , link "http://moltkeplatz.de" "" "http://moltkeplatz.de" + , "for", "fnords." + ]) + + , "Absolute file link" =: + "[[file:///etc/passwd][passwd]]" =?> + para (link "file:///etc/passwd" "" "passwd") + + , "File link" =: + "[[file:target][title]]" =?> + para (link "target" "" "title") + + , "Anchor" =: + "<> Link here later." =?> + para (spanWith ("anchor", [], []) mempty <> + "Link" <> space <> "here" <> space <> "later.") + + , "Inline code block" =: + "src_emacs-lisp{(message \"Hello\")}" =?> + para (codeWith ( "" + , [ "commonlisp" ] + , [ ("org-language", "emacs-lisp") ]) + "(message \"Hello\")") + + , "Inline code block with arguments" =: + "src_sh[:export both :results output]{echo 'Hello, World'}" =?> + para (codeWith ( "" + , [ "bash" ] + , [ ("org-language", "sh") + , ("export", "both") + , ("results", "output") + ] + ) + "echo 'Hello, World'") + + , "Inline code block with toggle" =: + "src_sh[:toggle]{echo $HOME}" =?> + para (codeWith ( "" + , [ "bash" ] + , [ ("org-language", "sh") + , ("toggle", "yes") + ] + ) + "echo $HOME") + + , "Inline LaTeX symbol" =: + "\\dots" =?> + para "…" + + , "Inline LaTeX command" =: + "\\textit{Emphasised}" =?> + para (emph "Emphasised") + + , "Inline LaTeX command with spaces" =: + "\\emph{Emphasis mine}" =?> + para (emph "Emphasis mine") + + , "Inline LaTeX math symbol" =: + "\\tau" =?> + para (emph "τ") + + , "Unknown inline LaTeX command" =: + "\\notacommand{foo}" =?> + para (rawInline "latex" "\\notacommand{foo}") + + , "Export snippet" =: + "@@html:M-x org-agenda@@" =?> + para (rawInline "html" "M-x org-agenda") + + , "MathML symbol in LaTeX-style" =: + "There is a hackerspace in Lübeck, Germany, called nbsp (unicode symbol: '\\nbsp')." =?> + para "There is a hackerspace in Lübeck, Germany, called nbsp (unicode symbol: ' ')." + + , "MathML symbol in LaTeX-style, including braces" =: + "\\Aacute{}stor" =?> + para "Ástor" + + , "MathML copy sign" =: + "\\copy" =?> + para "©" + + , "MathML symbols, space separated" =: + "\\ForAll \\Auml" =?> + para "∀ Ä" + + , "Macro" =: + T.unlines [ "#+MACRO: HELLO /Hello, $1/" + , "{{{HELLO(World)}}}" + ] =?> + para (emph "Hello, World") + + , "Macro repeting its argument" =: + T.unlines [ "#+MACRO: HELLO $1$1" + , "{{{HELLO(moin)}}}" + ] =?> + para "moinmoin" + + , "Macro called with too few arguments" =: + T.unlines [ "#+MACRO: HELLO Foo $1 $2 Bar" + , "{{{HELLO()}}}" + ] =?> + para "Foo Bar" + + , testGroup "Citations" Citation.tests + , testGroup "Footnotes" Note.tests + , testGroup "Smart punctuation" Smart.tests + ] diff --git a/test/Tests/Readers/Org/Inline/Citation.hs.orig b/test/Tests/Readers/Org/Inline/Citation.hs.orig new file mode 100644 index 000000000..d7e38a6b0 --- /dev/null +++ b/test/Tests/Readers/Org/Inline/Citation.hs.orig @@ -0,0 +1,179 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Readers.Org.Inline.Citation (tests) where + +import Test.Tasty (TestTree, testGroup) +import Tests.Helpers ((=?>)) +import Tests.Readers.Org.Shared ((=:)) +import Text.Pandoc.Builder + +tests :: [TestTree] +tests = + [ testGroup "Markdown-style citations" + [ "Citation" =: + "[@nonexistent]" =?> + let citation = Citation + { citationId = "nonexistent" + , citationPrefix = [] + , citationSuffix = [] + , citationMode = NormalCitation + , citationNoteNum = 0 + , citationHash = 0} + in (para $ cite [citation] "[@nonexistent]") + + , "Citation containing text" =: + "[see @item1 p. 34-35]" =?> + let citation = Citation + { citationId = "item1" + , citationPrefix = [Str "see"] + , citationSuffix = [Space ,Str "p.",Space,Str "34-35"] + , citationMode = NormalCitation + , citationNoteNum = 0 + , citationHash = 0} + in (para $ cite [citation] "[see @item1 p. 34-35]") + ] + + , testGroup "org-ref citations" + [ "simple citation" =: + "cite:pandoc" =?> + let citation = Citation + { citationId = "pandoc" + , citationPrefix = mempty + , citationSuffix = mempty + , citationMode = AuthorInText + , citationNoteNum = 0 + , citationHash = 0 + } + in (para $ cite [citation] "cite:pandoc") + + , "simple citation with underscores" =: + "cite:pandoc_org_ref" =?> + let citation = Citation + { citationId = "pandoc_org_ref" + , citationPrefix = mempty + , citationSuffix = mempty + , citationMode = AuthorInText + , citationNoteNum = 0 + , citationHash = 0 + } + in (para $ cite [citation] "cite:pandoc_org_ref") + + , "simple citation succeeded by comma" =: + "cite:pandoc," =?> + let citation = Citation + { citationId = "pandoc" + , citationPrefix = mempty + , citationSuffix = mempty + , citationMode = AuthorInText + , citationNoteNum = 0 + , citationHash = 0 + } + in (para $ cite [citation] "cite:pandoc" <> str ",") + + , "simple citation succeeded by dot" =: + "cite:pandoc." =?> + let citation = Citation + { citationId = "pandoc" + , citationPrefix = mempty + , citationSuffix = mempty + , citationMode = AuthorInText + , citationNoteNum = 0 + , citationHash = 0 + } + in (para $ cite [citation] "cite:pandoc" <> str ".") + + , "simple citation succeeded by colon" =: + "cite:pandoc:" =?> + let citation = Citation + { citationId = "pandoc" + , citationPrefix = mempty + , citationSuffix = mempty + , citationMode = AuthorInText + , citationNoteNum = 0 + , citationHash = 0 + } + in (para $ cite [citation] "cite:pandoc" <> str ":") + + , "simple citep citation" =: + "citep:pandoc" =?> + let citation = Citation + { citationId = "pandoc" + , citationPrefix = mempty + , citationSuffix = mempty + , citationMode = NormalCitation + , citationNoteNum = 0 + , citationHash = 0 + } + in (para $ cite [citation] "citep:pandoc") + + , "extended citation" =: + "[[citep:Dominik201408][See page 20::, for example]]" =?> + let citation = Citation + { citationId = "Dominik201408" + , citationPrefix = toList "See page 20" + , citationSuffix = toList ", for example" + , citationMode = NormalCitation + , citationNoteNum = 0 + , citationHash = 0 + } + in (para $ cite [citation] "[[citep:Dominik201408][See page 20::, for example]]") + ] + + , testGroup "Berkeley-style citations" $ + let pandocCite = Citation + { citationId = "Pandoc" + , citationPrefix = mempty + , citationSuffix = mempty + , citationMode = NormalCitation + , citationNoteNum = 0 + , citationHash = 0 + } + pandocInText = pandocCite { citationMode = AuthorInText } + dominikCite = Citation + { citationId = "Dominik201408" + , citationPrefix = mempty + , citationSuffix = mempty + , citationMode = NormalCitation + , citationNoteNum = 0 + , citationHash = 0 + } + dominikInText = dominikCite { citationMode = AuthorInText } + in + [ "Berkeley-style in-text citation" =: + "See @Dominik201408." =?> + para ("See " + <> cite [dominikInText] "@Dominik201408" + <> ".") + + , "Berkeley-style parenthetical citation list" =: + "[(cite): see; @Dominik201408;also @Pandoc; and others]" =?> + let pandocCite' = pandocCite { + citationPrefix = toList "also" + , citationSuffix = toList "and others" + } + dominikCite' = dominikCite { + citationPrefix = toList "see" + } + in (para $ cite [dominikCite', pandocCite'] "") + + , "Berkeley-style plain citation list" =: + "[cite: See; @Dominik201408; and @Pandoc; and others]" =?> + let pandocCite' = pandocInText { citationPrefix = toList "and" } + in (para $ "See " + <> cite [dominikInText] "" + <> "," <> space + <> cite [pandocCite'] "" + <> "," <> space <> "and others") + ] + + , "LaTeX citation" =: + "\\cite{Coffee}" =?> + let citation = Citation + { citationId = "Coffee" + , citationPrefix = [] + , citationSuffix = [] + , citationMode = NormalCitation + , citationNoteNum = 0 + , citationHash = 0} + in (para . cite [citation] $ rawInline "latex" "\\cite{Coffee}") + + ] diff --git a/test/Tests/Readers/Org/Inline/Note.hs.orig b/test/Tests/Readers/Org/Inline/Note.hs.orig new file mode 100644 index 000000000..9eb1d02d6 --- /dev/null +++ b/test/Tests/Readers/Org/Inline/Note.hs.orig @@ -0,0 +1,86 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Readers.Org.Inline.Note (tests) where + +import Test.Tasty (TestTree) +import Tests.Helpers ((=?>)) +import Tests.Readers.Org.Shared ((=:)) +import Text.Pandoc.Builder +import qualified Data.Text as T + +tests :: [TestTree] +tests = + [ "Footnote" =: + T.unlines [ "A footnote[1]" + , "" + , "[1] First paragraph" + , "" + , "second paragraph" + ] =?> + para (mconcat + [ "A", space, "footnote" + , note $ mconcat [ para ("First" <> space <> "paragraph") + , para ("second" <> space <> "paragraph") + ] + ]) + + , "Two footnotes" =: + T.unlines [ "Footnotes[fn:1][fn:2]" + , "" + , "[fn:1] First note." + , "" + , "[fn:2] Second note." + ] =?> + para (mconcat + [ "Footnotes" + , note $ para ("First" <> space <> "note.") + , note $ para ("Second" <> space <> "note.") + ]) + + , "Emphasized text before footnote" =: + T.unlines [ "/text/[fn:1]" + , "" + , "[fn:1] unicorn" + ] =?> + para (mconcat + [ emph "text" + , note . para $ "unicorn" + ]) + + , "Footnote that starts with emphasized text" =: + T.unlines [ "text[fn:1]" + , "" + , "[fn:1] /emphasized/" + ] =?> + para (mconcat + [ "text" + , note . para $ emph "emphasized" + ]) + + , "Footnote followed by header" =: + T.unlines [ "Another note[fn:yay]" + , "" + , "[fn:yay] This is great!" + , "" + , "** Headline" + ] =?> + mconcat + [ para (mconcat + [ "Another", space, "note" + , note $ para ("This" <> space <> "is" <> space <> "great!") + ]) + , headerWith ("headline", [], []) 2 "Headline" + ] + + , "Footnote followed by two blank lines" =: + T.unlines [ "footnote[fn:blanklines]" + , "" + , "[fn:blanklines] followed by blank lines" + , "" + , "" + , "next" + ] =?> + mconcat + [ para ("footnote" <> note (para "followed by blank lines")) + , para "next" + ] + ] diff --git a/test/Tests/Readers/Org/Inline/Smart.hs.orig b/test/Tests/Readers/Org/Inline/Smart.hs.orig new file mode 100644 index 000000000..77f10699d --- /dev/null +++ b/test/Tests/Readers/Org/Inline/Smart.hs.orig @@ -0,0 +1,46 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Readers.Org.Inline.Smart (tests) where + +import Data.Text (Text) +import Test.Tasty (TestTree) +import Tests.Helpers ((=?>), purely, test) +import Text.Pandoc (ReaderOptions (readerExtensions), + Extension (Ext_smart), def, enableExtension, + getDefaultExtensions, readOrg) +import Text.Pandoc.Builder + +orgSmart :: Text -> Pandoc +orgSmart = purely $ + let extensionsSmart = enableExtension Ext_smart (getDefaultExtensions "org") + in readOrg def{ readerExtensions = extensionsSmart } + +tests :: [TestTree] +tests = + [ test orgSmart "quote before ellipses" + ("'...hi'" + =?> para (singleQuoted "…hi")) + + , test orgSmart "apostrophe before emph" + ("D'oh! A l'/aide/!" + =?> para ("D’oh! A l’" <> emph "aide" <> "!")) + + , test orgSmart "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»") + + , test orgSmart "Quotes cannot occur at the end of emphasized text" + ("/say \"yes\"/" =?> + para ("/say" <> space <> doubleQuoted "yes" <> "/")) + + , test orgSmart "Dashes are allowed at the borders of emphasis'" + ("/foo---/" =?> + para (emph "foo—")) + + , test orgSmart "Single quotes can be followed by emphasized text" + ("Singles on the '/meat market/'" =?> + para ("Singles on the " <> singleQuoted (emph "meat market"))) + + , test orgSmart "Double quotes can be followed by emphasized text" + ("Double income, no kids: \"/DINK/\"" =?> + para ("Double income, no kids: " <> doubleQuoted (emph "DINK"))) + ] diff --git a/test/Tests/Readers/Org/Meta.hs.orig b/test/Tests/Readers/Org/Meta.hs.orig new file mode 100644 index 000000000..6bd1b02e7 --- /dev/null +++ b/test/Tests/Readers/Org/Meta.hs.orig @@ -0,0 +1,191 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Readers.Org.Meta (tests) where + +import Test.Tasty (TestTree, testGroup) +import Tests.Helpers ((=?>)) +import Tests.Readers.Org.Shared ((=:), spcSep) +import Text.Pandoc +import Text.Pandoc.Builder +import qualified Data.Text as T + +tests :: [TestTree] +tests = + [ "Comment" =: + "# Nothing to see here" =?> + (mempty::Blocks) + + , "Not a comment" =: + "#-tag" =?> + para "#-tag" + + , "Comment surrounded by Text" =: + T.unlines [ "Before" + , "# Comment" + , "After" + ] =?> + mconcat [ para "Before" + , para "After" + ] + + , "Title" =: + "#+TITLE: Hello, World" =?> + let titleInline = toList $ "Hello," <> space <> "World" + meta = setMeta "title" (MetaInlines titleInline) nullMeta + in Pandoc meta mempty + + , "Author" =: + "#+author: John /Emacs-Fanboy/ Doe" =?> + let author = toList . spcSep $ [ "John", emph "Emacs-Fanboy", "Doe" ] + meta = setMeta "author" (MetaList [MetaInlines author]) nullMeta + in Pandoc meta mempty + + , "Multiple authors" =: + "#+author: James Dewey Watson, Francis Harry Compton Crick " =?> + let watson = MetaInlines $ toList "James Dewey Watson" + crick = MetaInlines $ toList "Francis Harry Compton Crick" + meta = setMeta "author" (MetaList [watson, crick]) nullMeta + in Pandoc meta mempty + + , "Date" =: + "#+Date: Feb. *28*, 2014" =?> + let date = toList . spcSep $ [ "Feb.", strong "28" <> ",", "2014" ] + meta = setMeta "date" (MetaInlines date) nullMeta + in Pandoc meta mempty + + , "Description" =: + "#+DESCRIPTION: Explanatory text" =?> + let description = "Explanatory text" + meta = setMeta "description" (MetaString description) nullMeta + in Pandoc meta mempty + + , "Properties drawer" =: + T.unlines [ " :PROPERTIES:" + , " :setting: foo" + , " :END:" + ] =?> + (mempty::Blocks) + + , "LaTeX_headers options are translated to header-includes" =: + "#+LaTeX_header: \\usepackage{tikz}" =?> + let latexInlines = rawInline "latex" "\\usepackage{tikz}" + inclList = MetaList [MetaInlines (toList latexInlines)] + meta = setMeta "header-includes" inclList nullMeta + in Pandoc meta mempty + + , "LaTeX_class option is translated to documentclass" =: + "#+LATEX_CLASS: article" =?> + let meta = setMeta "documentclass" (MetaString "article") nullMeta + in Pandoc meta mempty + + , "LaTeX_class_options is translated to classoption" =: + "#+LATEX_CLASS_OPTIONS: [a4paper]" =?> + let meta = setMeta "classoption" (MetaString "a4paper") nullMeta + in Pandoc meta mempty + + , "LaTeX_class_options is translated to classoption" =: + "#+html_head: " =?> + let html = rawInline "html" "" + inclList = MetaList [MetaInlines (toList html)] + meta = setMeta "header-includes" inclList nullMeta + in Pandoc meta mempty + + , "later meta definitions take precedence" =: + T.unlines [ "#+AUTHOR: this will not be used" + , "#+author: Max" + ] =?> + let author = MetaInlines [Str "Max"] + meta = setMeta "author" (MetaList [author]) nullMeta + in Pandoc meta mempty + + , "Logbook drawer" =: + T.unlines [ " :LogBook:" + , " - State \"DONE\" from \"TODO\" [2014-03-03 Mon 11:00]" + , " :END:" + ] =?> + (mempty::Blocks) + + , "Drawer surrounded by text" =: + T.unlines [ "Before" + , ":PROPERTIES:" + , ":END:" + , "After" + ] =?> + para "Before" <> para "After" + + , "Drawer markers must be the only text in the line" =: + T.unlines [ " :LOGBOOK: foo" + , " :END: bar" + ] =?> + para (":LOGBOOK: foo" <> softbreak <> ":END: bar") + + , "Drawers can be arbitrary" =: + T.unlines [ ":FOO:" + , "/bar/" + , ":END:" + ] =?> + divWith (mempty, ["FOO", "drawer"], mempty) (para $ emph "bar") + + , "Anchor reference" =: + T.unlines [ "<> Target." + , "" + , "[[link-here][See here!]]" + ] =?> + (para (spanWith ("link-here", [], []) mempty <> "Target.") <> + para (link "#link-here" "" ("See" <> space <> "here!"))) + + , "Search links are read as emph" =: + "[[Wally][Where's Wally?]]" =?> + para (emph $ "Where's" <> space <> "Wally?") + + , "Link to nonexistent anchor" =: + T.unlines [ "<> Target." + , "" + , "[[link$here][See here!]]" + ] =?> + (para (spanWith ("link-here", [], []) mempty <> "Target.") <> + para (emph ("See" <> space <> "here!"))) + + , "Link abbreviation" =: + T.unlines [ "#+LINK: wp https://en.wikipedia.org/wiki/%s" + , "[[wp:Org_mode][Wikipedia on Org-mode]]" + ] =?> + para (link "https://en.wikipedia.org/wiki/Org_mode" "" + ("Wikipedia" <> space <> "on" <> space <> "Org-mode")) + + , "Link abbreviation, defined after first use" =: + T.unlines [ "[[zl:non-sense][Non-sense articles]]" + , "#+LINK: zl http://zeitlens.com/tags/%s.html" + ] =?> + para (link "http://zeitlens.com/tags/non-sense.html" "" + ("Non-sense" <> space <> "articles")) + + , "Link abbreviation, URL encoded arguments" =: + T.unlines [ "#+link: expl http://example.com/%h/foo" + , "[[expl:Hello, World!][Moin!]]" + ] =?> + para (link "http://example.com/Hello%2C%20World%21/foo" "" "Moin!") + + , "Link abbreviation, append arguments" =: + T.unlines [ "#+link: expl http://example.com/" + , "[[expl:foo][bar]]" + ] =?> + para (link "http://example.com/foo" "" "bar") + + , testGroup "emphasis config" + [ "Changing pre and post chars for emphasis" =: + T.unlines [ "#+pandoc-emphasis-pre: \"[)\"" + , "#+pandoc-emphasis-post: \"]\\n\"" + , "([/emph/])*foo*" + ] =?> + para ("([" <> emph "emph" <> "])" <> strong "foo") + + , "setting an invalid value restores the default" =: + T.unlines [ "#+pandoc-emphasis-pre: \"[\"" + , "#+pandoc-emphasis-post: \"]\"" + , "#+pandoc-emphasis-pre:" + , "#+pandoc-emphasis-post:" + , "[/noemph/]" + ] =?> + para ("[/noemph/]") + ] + ] diff --git a/test/Tests/Readers/Org/Shared.hs.orig b/test/Tests/Readers/Org/Shared.hs.orig new file mode 100644 index 000000000..5e8f6dd54 --- /dev/null +++ b/test/Tests/Readers/Org/Shared.hs.orig @@ -0,0 +1,29 @@ +module Tests.Readers.Org.Shared + ( (=:) + , org + , spcSep + , tagSpan + ) where + +import Data.List (intersperse) +import Data.Text (Text) +import Tests.Helpers (ToString, purely, test) +import Test.Tasty (TestTree) +import Text.Pandoc (Pandoc, ReaderOptions (readerExtensions), + def, getDefaultExtensions, readOrg) +import Text.Pandoc.Builder (Inlines, smallcaps, space, spanWith, str) + +org :: Text -> Pandoc +org = purely $ readOrg def{ readerExtensions = getDefaultExtensions "org" } + +infix 4 =: +(=:) :: ToString c + => String -> (Text, c) -> TestTree +(=:) = test org + +spcSep :: [Inlines] -> Inlines +spcSep = mconcat . intersperse space + +-- | Create a span for the given tag. +tagSpan :: String -> Inlines +tagSpan t = spanWith ("", ["tag"], [("tag-name", t)]) . smallcaps $ str t diff --git a/test/Tests/Readers/RST.hs.orig b/test/Tests/Readers/RST.hs.orig new file mode 100644 index 000000000..305c7060b --- /dev/null +++ b/test/Tests/Readers/RST.hs.orig @@ -0,0 +1,189 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE ScopedTypeVariables #-} +module Tests.Readers.RST (tests) where + +import Data.Text (Text) +import qualified Data.Text as T +import Test.Tasty +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder + +rst :: Text -> Pandoc +rst = purely $ readRST def{ readerStandalone = True } + +infix 4 =: +(=:) :: ToString c + => String -> (Text, c) -> TestTree +(=:) = test rst + +tests :: [TestTree] +tests = [ "line block with blank line" =: + "| a\n|\n| b" =?> lineBlock [ "a", mempty, "\160b" ] + , testGroup "field list" + [ "general" =: T.unlines + [ "para" + , "" + , ":Hostname: media08" + , ":IP address: 10.0.0.19" + , ":Size: 3ru" + , ":Version: 1" + , ":Indentation: Since the field marker may be quite long, the second" + , " and subsequent lines of the field body do not have to line up" + , " with the first line, but they must be indented relative to the" + , " field name marker, and they must line up with each other." + , ":Parameter i: integer" + , ":Final: item" + , " on two lines" ] + =?> + doc (para "para" <> + definitionList [ (str "Hostname", [para "media08"]) + , (text "IP address", [para "10.0.0.19"]) + , (str "Size", [para "3ru"]) + , (str "Version", [para "1"]) + , (str "Indentation", [para "Since the field marker may be quite long, the second\nand subsequent lines of the field body do not have to line up\nwith the first line, but they must be indented relative to the\nfield name marker, and they must line up with each other."]) + , (text "Parameter i", [para "integer"]) + , (str "Final", [para "item\non two lines"]) + ]) + , "metadata" =: T.unlines + [ "=====" + , "Title" + , "=====" + , "--------" + , "Subtitle" + , "--------" + , "" + , ":Version: 1" + ] + =?> + setMeta "version" (para "1") (setMeta "title" ("Title" :: Inlines) + $ setMeta "subtitle" ("Subtitle" :: Inlines) + $ doc mempty) + , "with inline markup" =: T.unlines + [ ":*Date*: today" + , "" + , ".." + , "" + , ":*one*: emphasis" + , ":two_: reference" + , ":`three`_: another one" + , ":``four``: literal" + , "" + , ".. _two: http://example.com" + , ".. _three: http://example.org" + ] + =?> + setMeta "date" (str "today") (doc + $ definitionList [ (emph "one", [para "emphasis"]) + , (link "http://example.com" "" "two", [para "reference"]) + , (link "http://example.org" "" "three", [para "another one"]) + , (code "four", [para "literal"]) + ]) + ] + , "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" <> ". " <> + softbreak <> + link "http://foo.bar/baz_(bam)" "" "http://foo.bar/baz_(bam)" + <> " (" <> link "http://foo.bar" "" "http://foo.bar" <> ")") + , "Reference names with special characters" =: + ("A-1-B_2_C:3:D+4+E.5.F_\n\n" <> + ".. _A-1-B_2_C:3:D+4+E.5.F: https://example.com\n") =?> + para (link "https://example.com" "" "A-1-B_2_C:3:D+4+E.5.F") + , "Code directive with class and number-lines" =: T.unlines + [ ".. code::python" + , " :number-lines: 34" + , " :class: class1 class2 class3" + , "" + , " def func(x):" + , " return y" + ] =?> + doc (codeBlockWith + ( "" + , ["sourceCode", "python", "numberLines", "class1", "class2", "class3"] + , [ ("startFrom", "34") ] + ) + "def func(x):\n return y") + , "Code directive with number-lines, no line specified" =: T.unlines + [ ".. code::python" + , " :number-lines: " + , "" + , " def func(x):" + , " return y" + ] =?> + doc (codeBlockWith + ( "" + , ["sourceCode", "python", "numberLines"] + , [ ("startFrom", "") ] + ) + "def func(x):\n return y") + , testGroup "literal / line / code blocks" + [ "indented literal block" =: T.unlines + [ "::" + , "" + , " block quotes" + , "" + , " can go on for many lines" + , "but must stop here"] + =?> + doc ( + codeBlock "block quotes\n\ncan go on for many lines" <> + para "but must stop here") + , "line block with 3 lines" =: "| a\n| b\n| c" + =?> lineBlock ["a", "b", "c"] + , "line blocks with blank lines" =: T.unlines + [ "|" + , "" + , "|" + , "| a" + , "| b" + , "|" + , "" + , "|" + ] =?> + lineBlock [""] <> + lineBlock ["", "a", "b", ""] <> + lineBlock [""] + , "quoted literal block using >" =: "::\n\n> quoted\n> block\n\nOrdinary paragraph" + =?> codeBlock "> quoted\n> block" <> para "Ordinary paragraph" + , "quoted literal block using | (not a line block)" =: "::\n\n| quoted\n| block\n\nOrdinary paragraph" + =?> codeBlock "| quoted\n| block" <> para "Ordinary paragraph" + , "class directive with single paragraph" =: ".. class:: special\n\nThis is a \"special\" paragraph." + =?> divWith ("", ["special"], []) (para "This is a \"special\" paragraph.") + , "class directive with two paragraphs" =: ".. class:: exceptional remarkable\n\n First paragraph.\n\n Second paragraph." + =?> divWith ("", ["exceptional", "remarkable"], []) (para "First paragraph." <> para "Second paragraph.") + , "class directive around literal block" =: ".. class:: classy\n\n::\n\n a\n b" + =?> divWith ("", ["classy"], []) (codeBlock "a\nb")] + , testGroup "interpreted text roles" + [ "literal role prefix" =: ":literal:`a`" =?> para (code "a") + , "literal role postfix" =: "`a`:literal:" =?> para (code "a") + , "literal text" =: "``text``" =?> para (code "text") + , "code role" =: ":code:`a`" =?> para (codeWith ("", ["sourceCode"], []) "a") + , "inherited code role" =: ".. role:: codeLike(code)\n\n:codeLike:`a`" + =?> para (codeWith ("", ["codeLike", "sourceCode"], []) "a") + , "custom code role with language field" + =: ".. role:: lhs(code)\n :language: haskell\n\n:lhs:`a`" + =?> para (codeWith ("", ["lhs", "haskell","sourceCode"], []) "a") + , "custom role with unspecified parent role" + =: ".. role:: classy\n\n:classy:`text`" + =?> para (spanWith ("", ["classy"], []) "text") + , "role with recursive inheritance" + =: ".. role:: haskell(code)\n.. role:: lhs(haskell)\n\n:lhs:`text`" + =?> para (codeWith ("", ["lhs", "haskell", "sourceCode"], []) "text") + , "unknown role" =: ":unknown:`text`" =?> + para (spanWith ("",[],[("role","unknown")]) (str "text")) + ] + , testGroup "footnotes" + [ "remove space before note" =: T.unlines + [ "foo [1]_" + , "" + , ".. [1]" + , " bar" + ] =?> + para ("foo" <> note (para "bar")) + ] + ] diff --git a/test/Tests/Readers/Txt2Tags.hs.orig b/test/Tests/Readers/Txt2Tags.hs.orig new file mode 100644 index 000000000..e3646e95e --- /dev/null +++ b/test/Tests/Readers/Txt2Tags.hs.orig @@ -0,0 +1,437 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Readers.Txt2Tags (tests) where + +import Data.List (intersperse) +import Data.Text (Text) +import qualified Data.Text as T +import Test.Tasty +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder +import Text.Pandoc.Shared (underlineSpan) + +t2t :: Text -> Pandoc +-- t2t = handleError . readTxt2Tags (T2TMeta "date" "mtime" "in" "out") def +t2t = purely $ \s -> do + setInputFiles ["in"] + setOutputFile (Just "out") + readTxt2Tags def s + +infix 4 =: +(=:) :: ToString c + => String -> (Text, c) -> TestTree +(=:) = test t2t + +spcSep :: [Inlines] -> Inlines +spcSep = mconcat . intersperse space + +simpleTable' :: Int + -> [Blocks] + -> [[Blocks]] + -> Blocks +simpleTable' n = table "" (replicate n (AlignCenter, 0.0)) + +tests :: [TestTree] +tests = + [ testGroup "Inlines" + [ "Plain String" =: + "Hello, World" =?> + para (spcSep [ "Hello,", "World" ]) + + , "Emphasis" =: + "//Planet Punk//" =?> + para (emph . spcSep $ ["Planet", "Punk"]) + + , "Strong" =: + "**Cider**" =?> + para (strong "Cider") + + , "Strong Emphasis" =: + "//**strength**//" =?> + para (emph . strong $ "strength") + + , "Strikeout" =: + "--Kill Bill--" =?> + para (strikeout . spcSep $ [ "Kill", "Bill" ]) + + , "Verbatim" =: + "``Robot.rock()``" =?> + para (code "Robot.rock()") + + , "Symbol" =: + "A * symbol" =?> + para (str "A" <> space <> str "*" <> space <> "symbol") + + , "No empty markup" =: + "//// **** ____ ---- ```` \"\"\"\" ''''" =?> + para (spcSep [ "////", "****", "____", "----", "````", "\"\"\"\"", "''''" ]) + + , "Inline markup is greedy" =: + "***** ///// _____ ----- ````` \"\"\"\"\" '''''" =?> + para (spcSep [strong "*", emph "/", underlineSpan "_" + , strikeout "-", code "`", text "\"" + , rawInline "html" "'"]) + , "Markup must be greedy" =: + "********** ////////// __________ ---------- `````````` \"\"\"\"\"\"\"\"\"\" ''''''''''" =?> + para (spcSep [strong "******", emph "//////", underlineSpan "______" + , strikeout "------", code "``````", text "\"\"\"\"\"\"" + , rawInline "html" "''''''"]) + , "Inlines must be glued" =: + "** a** **a ** ** a **" =?> + para (text "** a** **a ** ** a **") + + , "Macros: Date" =: + "%%date" =?> + para "1970-01-01" + , "Macros: Mod Time" =: + "%%mtime" =?> + para (str "") + , "Macros: Infile" =: + "%%infile" =?> + para "in" + , "Macros: Outfile" =: + "%%outfile" =?> + para "out" + , "Autolink" =: + "http://www.google.com" =?> + para (link "http://www.google.com" "" (str "http://www.google.com")) + , "JPEG Image" =: + "[image.jpg]" =?> + para (image "image.jpg" "" mempty) + , "PNG Image" =: + "[image.png]" =?> + para (image "image.png" "" mempty) + + , "Link" =: + "[title http://google.com]" =?> + para (link "http://google.com" "" (str "title")) + + , "Image link" =: + "[[image.jpg] abc]" =?> + para (link "abc" "" (image "image.jpg" "" mempty)) + , "Invalid link: No trailing space" =: + "[title invalid ]" =?> + para (text "[title invalid ]") + + + ] + + , testGroup "Basic Blocks" + ["Paragraph, lines grouped together" =: + "A paragraph\n A blank line ends the \n current paragraph\n" + =?> para "A paragraph\n A blank line ends the\n current paragraph" + , "Paragraph, ignore leading and trailing spaces" =: + " Leading and trailing spaces are ignored. \n" =?> + para "Leading and trailing spaces are ignored." + , "Comment line in paragraph" =: + "A comment line can be placed inside a paragraph.\n% this comment will be ignored \nIt will not affect it.\n" + =?> para "A comment line can be placed inside a paragraph.\nIt will not affect it." + , "Paragraph" =: + "Paragraph\n" =?> + para "Paragraph" + + , "First Level Header" =: + "+ Headline +\n" =?> + header 1 "Headline" + + , "Third Level Header" =: + "=== Third Level Headline ===\n" =?> + header 3 ("Third" <> space <> + "Level" <> space <> + "Headline") + + , "Header with label" =: + "= header =[label]" =?> + headerWith ("label", [], []) 1 "header" + + , "Invalid header, mismatched delimiters" =: + "== header =" =?> + para (text "== header =") + + , "Invalid header, spaces in label" =: + "== header ==[ haha ]" =?> + para (text "== header ==[ haha ]") + + , "Invalid header, invalid label character" =: + "== header ==[lab/el]" =?> + para (text "== header ==[lab/el]") + , "Headers not preceded by a blank line" =: + T.unlines [ "++ eat dinner ++" + , "Spaghetti and meatballs tonight." + , "== walk dog ==" + ] =?> + mconcat [ header 2 ("eat" <> space <> "dinner") + , para $ spcSep [ "Spaghetti", "and", "meatballs", "tonight." ] + , header 2 ("walk" <> space <> "dog") + ] + + , "Paragraph starting with an equals" =: + "=five" =?> + para "=five" + + , "Paragraph containing asterisk at beginning of line" =: + T.unlines [ "lucky" + , "*star" + ] =?> + para ("lucky" <> softbreak <> "*star") + + , "Horizontal Rule" =: + T.unlines [ "before" + , T.replicate 20 "-" + , T.replicate 20 "=" + , T.replicate 20 "_" + , "after" + ] =?> + mconcat [ para "before" + , horizontalRule + , horizontalRule + , horizontalRule + , para "after" + ] + + , "Comment Block" =: + T.unlines [ "%%%" + , "stuff" + , "bla" + , "%%%"] =?> + (mempty::Blocks) + + + ] + + , testGroup "Lists" + [ "Simple Bullet Lists" =: + ("- Item1\n" <> + "- Item2\n") =?> + bulletList [ plain "Item1" + , plain "Item2" + ] + + , "Indented Bullet Lists" =: + (" - Item1\n" <> + " - Item2\n") =?> + bulletList [ plain "Item1" + , plain "Item2" + ] + + + + , "Nested Bullet Lists" =: + ("- Discovery\n" <> + " + One More Time\n" <> + " + Harder, Better, Faster, Stronger\n" <> + "- Homework\n" <> + " + Around the World\n"<> + "- Human After All\n" <> + " + Technologic\n" <> + " + Robot Rock\n") =?> + bulletList [ mconcat + [ plain "Discovery" + , orderedList [ plain ("One" <> space <> + "More" <> space <> + "Time") + , plain ("Harder," <> space <> + "Better," <> space <> + "Faster," <> space <> + "Stronger") + ] + ] + , mconcat + [ plain "Homework" + , orderedList [ plain ("Around" <> space <> + "the" <> space <> + "World") + ] + ] + , mconcat + [ plain ("Human" <> space <> "After" <> space <> "All") + , orderedList [ plain "Technologic" + , plain ("Robot" <> space <> "Rock") + ] + ] + ] + + , "Simple Ordered List" =: + ("+ Item1\n" <> + "+ Item2\n") =?> + let listStyle = (1, DefaultStyle, DefaultDelim) + listStructure = [ plain "Item1" + , plain "Item2" + ] + in orderedListWith listStyle listStructure + + + , "Indented Ordered List" =: + (" + Item1\n" <> + " + Item2\n") =?> + let listStyle = (1, DefaultStyle, DefaultDelim) + listStructure = [ plain "Item1" + , plain "Item2" + ] + in orderedListWith listStyle listStructure + + , "Nested Ordered Lists" =: + ("+ One\n" <> + " + One-One\n" <> + " + One-Two\n" <> + "+ Two\n" <> + " + Two-One\n"<> + " + Two-Two\n") =?> + let listStyle = (1, DefaultStyle, DefaultDelim) + listStructure = [ mconcat + [ plain "One" + , orderedList [ plain "One-One" + , plain "One-Two" + ] + ] + , mconcat + [ plain "Two" + , orderedList [ plain "Two-One" + , plain "Two-Two" + ] + ] + ] + in orderedListWith listStyle listStructure + + , "Ordered List in Bullet List" =: + ("- Emacs\n" <> + " + Org\n") =?> + bulletList [ (plain "Emacs") <> + (orderedList [ plain "Org"]) + ] + + , "Bullet List in Ordered List" =: + ("+ GNU\n" <> + " - Freedom\n") =?> + orderedList [ (plain "GNU") <> bulletList [ (plain "Freedom") ] ] + + , "Definition List" =: + T.unlines [ ": PLL" + , " phase-locked loop" + , ": TTL" + , " transistor-transistor logic" + , ": PSK" + , " a digital" + ] =?> + definitionList [ ("PLL", [ plain $ "phase-locked" <> space <> "loop" ]) + , ("TTL", [ plain $ "transistor-transistor" <> space <> "logic" ]) + , ("PSK", [ plain $ "a" <> space <> "digital" ]) + ] + + + , "Loose bullet list" =: + T.unlines [ "- apple" + , "" + , "- orange" + , "" + , "- peach" + ] =?> + bulletList [ para "apple" + , para "orange" + , para "peach" + ] + ] + + , testGroup "Tables" + [ "Single cell table" =: + "| Test " =?> + simpleTable' 1 mempty [[plain "Test"]] + + , "Multi cell table" =: + "| One | Two |" =?> + simpleTable' 2 mempty [ [ plain "One", plain "Two" ] ] + + , "Multi line table" =: + T.unlines [ "| One |" + , "| Two |" + , "| Three |" + ] =?> + simpleTable' 1 mempty + [ [ plain "One" ] + , [ plain "Two" ] + , [ plain "Three" ] + ] + + , "Empty table" =: + "| |" =?> + simpleTable' 1 mempty [[mempty]] + + , "Glider Table" =: + T.unlines [ "| 1 | 0 | 0 |" + , "| 0 | 1 | 1 |" + , "| 1 | 1 | 0 |" + ] =?> + simpleTable' 3 mempty + [ [ plain "1", plain "0", plain "0" ] + , [ plain "0", plain "1", plain "1" ] + , [ plain "1", plain "1", plain "0" ] + ] + + + , "Table with Header" =: + T.unlines [ "|| Species | Status |" + , "| cervisiae | domesticated |" + , "| paradoxus | wild |" + ] =?> + simpleTable [ plain "Species", plain "Status" ] + [ [ plain "cervisiae", plain "domesticated" ] + , [ plain "paradoxus", plain "wild" ] + ] + + , "Table alignment determined by spacing" =: + T.unlines [ "| Numbers | Text | More |" + , "| 1 | One | foo |" + , "| 2 | Two | bar |" + ] =?> + table "" (zip [AlignCenter, AlignRight, AlignDefault] [0, 0, 0]) + [] + [ [ plain "Numbers", plain "Text", plain "More" ] + , [ plain "1" , plain "One" , plain "foo" ] + , [ plain "2" , plain "Two" , plain "bar" ] + ] + + , "Pipe within text doesn't start a table" =: + "Ceci n'est pas une | pipe " =?> + para (spcSep [ "Ceci", "n'est", "pas", "une", "|", "pipe" ]) + + + , "Table with differing row lengths" =: + T.unlines [ "|| Numbers | Text " + , "| 1 | One | foo |" + , "| 2 " + ] =?> + table "" (zip [AlignCenter, AlignLeft, AlignLeft] [0, 0, 0]) + [ plain "Numbers", plain "Text" , plain mempty ] + [ [ plain "1" , plain "One" , plain "foo" ] + , [ plain "2" , plain mempty , plain mempty ] + ] + + ] + + , testGroup "Blocks and fragments" + [ "Source block" =: + T.unlines [ "```" + , "main = putStrLn greeting" + , " where greeting = \"moin\"" + , "```" ] =?> + let code' = "main = putStrLn greeting\n" <> + " where greeting = \"moin\"\n" + in codeBlock code' + + , "tagged block" =: + T.unlines [ "'''" + , "" + , "'''" + ] =?> + rawBlock "html" "\n" + + , "Quote block" =: + T.unlines ["\t//Niemand// hat die Absicht, eine Mauer zu errichten!" + ] =?> + blockQuote (para (spcSep [ emph "Niemand", "hat", "die", "Absicht," + , "eine", "Mauer", "zu", "errichten!" + ])) + + ] + ] diff --git a/test/Tests/Shared.hs.orig b/test/Tests/Shared.hs.orig new file mode 100644 index 000000000..cc448419c --- /dev/null +++ b/test/Tests/Shared.hs.orig @@ -0,0 +1,39 @@ +module Tests.Shared (tests) where + +import System.FilePath.Posix (joinPath) +import Test.Tasty +import Test.Tasty.HUnit (assertBool, testCase, (@?=)) +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder +import Text.Pandoc.Shared + +tests :: [TestTree] +tests = [ testGroup "compactifyDL" + [ testCase "compactifyDL with empty def" $ + assertBool "compactifyDL" + (let x = [(str "word", [para (str "def"), mempty])] + in compactifyDL x == x) + ] + , testGroup "collapseFilePath" testCollapse + ] + +testCollapse :: [TestTree] +testCollapse = map (testCase "collapse") + [ collapseFilePath (joinPath [ ""]) @?= (joinPath [ ""]) + , collapseFilePath (joinPath [ ".","foo"]) @?= (joinPath [ "foo"]) + , collapseFilePath (joinPath [ ".",".","..","foo"]) @?= (joinPath [ joinPath ["..", "foo"]]) + , collapseFilePath (joinPath [ "..","foo"]) @?= (joinPath [ "..","foo"]) + , collapseFilePath (joinPath [ "","bar","..","baz"]) @?= (joinPath [ "","baz"]) + , collapseFilePath (joinPath [ "","..","baz"]) @?= (joinPath [ "","..","baz"]) + , collapseFilePath (joinPath [ ".","foo","..",".","bar","..",".",".","baz"]) @?= (joinPath [ "baz"]) + , collapseFilePath (joinPath [ ".",""]) @?= (joinPath [ ""]) + , collapseFilePath (joinPath [ ".",".",""]) @?= (joinPath [ ""]) + , collapseFilePath (joinPath [ "..",""]) @?= (joinPath [ ".."]) + , collapseFilePath (joinPath [ "..",".",""]) @?= (joinPath [ ".."]) + , collapseFilePath (joinPath [ ".","..",""]) @?= (joinPath [ ".."]) + , collapseFilePath (joinPath [ "..","..",""]) @?= (joinPath [ "..",".."]) + , collapseFilePath (joinPath [ "parent","foo","baz","..","bar"]) @?= (joinPath [ "parent","foo","bar"]) + , collapseFilePath (joinPath [ "parent","foo","baz","..","..","bar"]) @?= (joinPath [ "parent","bar"]) + , collapseFilePath (joinPath [ "parent","foo",".."]) @?= (joinPath [ "parent"]) + , collapseFilePath (joinPath [ "","parent","foo","..","..","bar"]) @?= (joinPath [ "","bar"]) + , collapseFilePath (joinPath [ "",".","parent","foo"]) @?= (joinPath [ "","parent","foo"])] diff --git a/test/Tests/Writers/AsciiDoc.hs.orig b/test/Tests/Writers/AsciiDoc.hs.orig new file mode 100644 index 000000000..6b97c0761 --- /dev/null +++ b/test/Tests/Writers/AsciiDoc.hs.orig @@ -0,0 +1,56 @@ +module Tests.Writers.AsciiDoc (tests) where + +import Data.Text (unpack) +import Test.Tasty +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder + +asciidoc :: (ToPandoc a) => a -> String +asciidoc = unpack . purely (writeAsciiDoc def{ writerWrapText = WrapNone }) . toPandoc + +tests :: [TestTree] +tests = [ testGroup "emphasis" + [ test asciidoc "emph word before" $ + para (text "foo" <> emph (text "bar")) =?> + "foo__bar__" + , test asciidoc "emph word after" $ + para (emph (text "foo") <> text "bar") =?> + "__foo__bar" + , test asciidoc "emph quoted" $ + para (doubleQuoted (emph (text "foo"))) =?> + "``__foo__''" + , test asciidoc "strong word before" $ + para (text "foo" <> strong (text "bar")) =?> + "foo**bar**" + , test asciidoc "strong word after" $ + para (strong (text "foo") <> text "bar") =?> + "**foo**bar" + , test asciidoc "strong quoted" $ + para (singleQuoted (strong (text "foo"))) =?> + "`**foo**'" + ] + , testGroup "tables" + [ test asciidoc "empty cells" $ + simpleTable [] [[mempty],[mempty]] =?> unlines + [ "[cols=\"\",]" + , "|====" + , "|" + , "|" + , "|====" + ] + , test asciidoc "multiblock cells" $ + simpleTable [] [[para (text "Para 1") <> para (text "Para 2")]] + =?> unlines + [ "[cols=\"\",]" + , "|=====" + , "a|" + , "Para 1" + , "" + , "Para 2" + , "" + , "|=====" + ] + ] + ] diff --git a/test/Tests/Writers/ConTeXt.hs.orig b/test/Tests/Writers/ConTeXt.hs.orig new file mode 100644 index 000000000..812aab4a6 --- /dev/null +++ b/test/Tests/Writers/ConTeXt.hs.orig @@ -0,0 +1,149 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.ConTeXt (tests) where + +import Data.Text (unpack) +import Test.Tasty +import Test.Tasty.QuickCheck +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder + +context :: (ToPandoc a) => a -> String +context = unpack . purely (writeConTeXt def) . toPandoc + +context' :: (ToPandoc a) => a -> String +context' = unpack . purely (writeConTeXt def{ writerWrapText = WrapNone }) . toPandoc + +contextNtb :: (ToPandoc a) => a -> String +contextNtb = unpack . purely (writeConTeXt def{ writerExtensions = enableExtension Ext_ntb pandocExtensions }) . toPandoc + +contextDiv :: (ToPandoc a) => a -> String +contextDiv = unpack . purely (writeConTeXt def{ writerSectionDivs = True }) . toPandoc + +{- + "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 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> TestTree +(=:) = test context + +tests :: [TestTree] +tests = [ testGroup "inline code" + [ "with '}'" =: code "}" =?> "\\mono{\\}}" + , "without '}'" =: code "]" =?> "\\type{]}" + , testProperty "code property" $ \s -> null s || + if '{' `elem` s || '}' `elem` s + then context' (code s) == "\\mono{" ++ + context' (str s) ++ "}" + else context' (code s) == "\\type{" ++ s ++ "}" + ] + , testGroup "headers" + [ "level 1" =: + headerWith ("my-header",[],[]) 1 "My header" =?> "\\section[title={My header},reference={my-header}]" + , test contextDiv "section-divs" $ + ( headerWith ("header1", [], []) 1 (text "Header1") + <> headerWith ("header2", [], []) 2 (text "Header2") + <> headerWith ("header3", [], []) 3 (text "Header3") + <> headerWith ("header4", [], []) 4 (text "Header4") + <> headerWith ("header5", [], []) 5 (text "Header5") + <> headerWith ("header6", [], []) 6 (text "Header6")) + =?> + unlines [ "\\startsection[title={Header1},reference={header1}]\n" + , "\\startsubsection[title={Header2},reference={header2}]\n" + , "\\startsubsubsection[title={Header3},reference={header3}]\n" + , "\\startsubsubsubsection[title={Header4},reference={header4}]\n" + , "\\startsubsubsubsubsection[title={Header5},reference={header5}]\n" + , "\\startsubsubsubsubsubsection[title={Header6},reference={header6}]\n" + , "\\stopsubsubsubsubsubsection\n" + , "\\stopsubsubsubsubsection\n" + , "\\stopsubsubsubsection\n" + , "\\stopsubsubsection\n" + , "\\stopsubsection\n" + , "\\stopsection" ] + ] + , testGroup "bullet lists" + [ "nested" =: + bulletList [ + plain (text "top") + <> bulletList [ + plain (text "next") + <> bulletList [plain (text "bot")] + ] + ] =?> unlines + [ "\\startitemize[packed]" + , "\\item" + , " top" + , " \\startitemize[packed]" + , " \\item" + , " next" + , " \\startitemize[packed]" + , " \\item" + , " bot" + , " \\stopitemize" + , " \\stopitemize" + , "\\stopitemize" ] + ] + , testGroup "natural tables" + [ test contextNtb "table with header and caption" $ + let caption = text "Table 1" + aligns = [(AlignRight, 0.0), (AlignLeft, 0.0), (AlignCenter, 0.0), (AlignDefault, 0.0)] + headers = [plain $ text "Right", + plain $ text "Left", + plain $ text "Center", + plain $ text "Default"] + rows = [[plain $ text "1.1", + plain $ text "1.2", + plain $ text "1.3", + plain $ text "1.4"] + ,[plain $ text "2.1", + plain $ text "2.2", + plain $ text "2.3", + plain $ text "2.4"] + ,[plain $ text "3.1", + plain $ text "3.2", + plain $ text "3.3", + plain $ text "3.4"]] + in table caption aligns headers rows + =?> unlines [ "\\startplacetable[title={Table 1}]" + , "\\startTABLE" + , "\\startTABLEhead" + , "\\NC[align=left] Right" + , "\\NC[align=right] Left" + , "\\NC[align=middle] Center" + , "\\NC Default" + , "\\NC\\NR" + , "\\stopTABLEhead" + , "\\startTABLEbody" + , "\\NC[align=left] 1.1" + , "\\NC[align=right] 1.2" + , "\\NC[align=middle] 1.3" + , "\\NC 1.4" + , "\\NC\\NR" + , "\\NC[align=left] 2.1" + , "\\NC[align=right] 2.2" + , "\\NC[align=middle] 2.3" + , "\\NC 2.4" + , "\\NC\\NR" + , "\\stopTABLEbody" + , "\\startTABLEfoot" + , "\\NC[align=left] 3.1" + , "\\NC[align=right] 3.2" + , "\\NC[align=middle] 3.3" + , "\\NC 3.4" + , "\\NC\\NR" + , "\\stopTABLEfoot" + , "\\stopTABLE" + , "\\stopplacetable" ] + ] + ] diff --git a/test/Tests/Writers/Docbook.hs.orig b/test/Tests/Writers/Docbook.hs.orig new file mode 100644 index 000000000..89ea76586 --- /dev/null +++ b/test/Tests/Writers/Docbook.hs.orig @@ -0,0 +1,303 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.Docbook (tests) where + +import Data.Text (unpack) +import Test.Tasty +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder + +docbook :: (ToPandoc a) => a -> String +docbook = docbookWithOpts def{ writerWrapText = WrapNone } + +docbookWithOpts :: ToPandoc a => WriterOptions -> a -> String +docbookWithOpts opts = unpack . purely (writeDocbook4 opts) . toPandoc + +{- + "my test" =: X =?> Y + +is shorthand for + + test docbook "my test" $ X =?> Y + +which is in turn shorthand for + + test docbook "my test" (X,Y) +-} + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> TestTree +(=:) = test docbook + +lineblock :: Blocks +lineblock = para ("some text" <> linebreak <> + "and more lines" <> linebreak <> + "and again") +lineblock_out :: [String] +lineblock_out = [ "some text" + , "and more lines" + , "and again" + ] + +tests :: [TestTree] +tests = [ testGroup "line blocks" + [ "none" =: para "This is a test" + =?> unlines + [ "" + , " This is a test" + , "" + ] + , "basic" =: lineblock + =?> unlines lineblock_out + , "blockquote" =: blockQuote lineblock + =?> unlines + ( [ "
" ] ++ + lineblock_out ++ + [ "
" ] + ) + , "footnote" =: para ("This is a test" <> + note lineblock <> + " of footnotes") + =?> unlines + ( [ "" + , " This is a test" ] ++ + lineblock_out ++ + [ " of footnotes" + , "" ] + ) + ] + , testGroup "compact lists" + [ testGroup "bullet" + [ "compact" =: bulletList [plain "a", plain "b", plain "c"] + =?> unlines + [ "" + , " " + , " " + , " a" + , " " + , " " + , " " + , " " + , " b" + , " " + , " " + , " " + , " " + , " c" + , " " + , " " + , "" + ] + , "loose" =: bulletList [para "a", para "b", para "c"] + =?> unlines + [ "" + , " " + , " " + , " a" + , " " + , " " + , " " + , " " + , " b" + , " " + , " " + , " " + , " " + , " c" + , " " + , " " + , "" + ] + ] + , testGroup "ordered" + [ "compact" =: orderedList [plain "a", plain "b", plain "c"] + =?> unlines + [ "" + , " " + , " " + , " a" + , " " + , " " + , " " + , " " + , " b" + , " " + , " " + , " " + , " " + , " c" + , " " + , " " + , "" + ] + , "loose" =: orderedList [para "a", para "b", para "c"] + =?> unlines + [ "" + , " " + , " " + , " a" + , " " + , " " + , " " + , " " + , " b" + , " " + , " " + , " " + , " " + , " c" + , " " + , " " + , "" + ] + ] + , testGroup "definition" + [ "compact" =: definitionList [ ("an", [plain "apple" ]) + , ("a", [plain "banana"]) + , ("an", [plain "orange"])] + =?> unlines + [ "" + , " " + , " " + , " an" + , " " + , " " + , " " + , " apple" + , " " + , " " + , " " + , " " + , " " + , " a" + , " " + , " " + , " " + , " banana" + , " " + , " " + , " " + , " " + , " " + , " an" + , " " + , " " + , " " + , " orange" + , " " + , " " + , " " + , "" + ] + , "loose" =: definitionList [ ("an", [para "apple" ]) + , ("a", [para "banana"]) + , ("an", [para "orange"])] + =?> unlines + [ "" + , " " + , " " + , " an" + , " " + , " " + , " " + , " apple" + , " " + , " " + , " " + , " " + , " " + , " a" + , " " + , " " + , " " + , " banana" + , " " + , " " + , " " + , " " + , " " + , " an" + , " " + , " " + , " " + , " orange" + , " " + , " " + , " " + , "" + ] + ] + ] + , testGroup "writer options" + [ testGroup "top-level division" $ + let + headers = header 1 (text "header1") + <> header 2 (text "header2") + <> header 3 (text "header3") + + docbookTopLevelDiv :: (ToPandoc a) + => TopLevelDivision -> a -> String + docbookTopLevelDiv division = + docbookWithOpts def{ writerTopLevelDivision = division } + in + [ test (docbookTopLevelDiv TopLevelSection) "sections as top-level" $ + headers =?> + unlines [ "" + , " header1" + , " " + , " header2" + , " " + , " header3" + , " " + , " " + , " " + , " " + , "" + ] + , test (docbookTopLevelDiv TopLevelChapter) "chapters as top-level" $ + headers =?> + unlines [ "" + , " header1" + , " " + , " header2" + , " " + , " header3" + , " " + , " " + , " " + , " " + , "" + ] + , test (docbookTopLevelDiv TopLevelPart) "parts as top-level" $ + headers =?> + unlines [ "" + , " header1" + , " " + , " header2" + , " " + , " header3" + , " " + , " " + , " " + , " " + , "" + ] + , test (docbookTopLevelDiv TopLevelDefault) "default top-level" $ + headers =?> + unlines [ "" + , " header1" + , " " + , " header2" + , " " + , " header3" + , " " + , " " + , " " + , " " + , "" + ] + ] + ] + ] diff --git a/test/Tests/Writers/Docx.hs.orig b/test/Tests/Writers/Docx.hs.orig new file mode 100644 index 000000000..3ded0aa38 --- /dev/null +++ b/test/Tests/Writers/Docx.hs.orig @@ -0,0 +1,157 @@ +module Tests.Writers.Docx (tests) where + +import Text.Pandoc +import Test.Tasty +import Tests.Writers.OOXML +import Test.Tasty.HUnit +import Data.List (isPrefixOf) + +-- we add an extra check to make sure that we're not writing in the +-- toplevel docx directory. We don't want to accidentally overwrite an +-- Word-generated docx file used to test the reader. +docxTest :: String -> WriterOptions -> FilePath -> FilePath -> TestTree +docxTest testName opts nativeFP goldenFP = + if "docx/golden/" `isPrefixOf` goldenFP + then ooxmlTest writeDocx testName opts nativeFP goldenFP + else testCase testName $ + assertFailure $ + goldenFP ++ " is not in `test/docx/golden`" + +tests :: [TestTree] +tests = [ testGroup "inlines" + [ docxTest + "font formatting" + def + "docx/inline_formatting.native" + "docx/golden/inline_formatting.docx" + , docxTest + "hyperlinks" + def + "docx/links.native" + "docx/golden/links.docx" + , docxTest + "inline image" + def + "docx/image_writer_test.native" + "docx/golden/image.docx" + , docxTest + "inline images" + def + "docx/inline_images_writer_test.native" + "docx/golden/inline_images.docx" + , docxTest + "handling unicode input" + def + "docx/unicode.native" + "docx/golden/unicode.docx" + , docxTest + "inline code" + def + "docx/inline_code.native" + "docx/golden/inline_code.docx" + , docxTest + "inline code in subscript and superscript" + def + "docx/verbatim_subsuper.native" + "docx/golden/verbatim_subsuper.docx" + ] + , testGroup "blocks" + [ docxTest + "headers" + def + "docx/headers.native" + "docx/golden/headers.docx" + , docxTest + "nested anchor spans in header" + def + "docx/nested_anchors_in_header.native" + "docx/golden/nested_anchors_in_header.docx" + , docxTest + "lists" + def + "docx/lists.native" + "docx/golden/lists.docx" + , docxTest + "lists continuing after interruption" + def + "docx/lists_continuing.native" + "docx/golden/lists_continuing.docx" + , docxTest + "lists restarting after interruption" + def + "docx/lists_restarting.native" + "docx/golden/lists_restarting.docx" + , docxTest + "definition lists" + def + "docx/definition_list.native" + "docx/golden/definition_list.docx" + , docxTest + "footnotes and endnotes" + def + "docx/notes.native" + "docx/golden/notes.docx" + , docxTest + "links in footnotes and endnotes" + def + "docx/link_in_notes.native" + "docx/golden/link_in_notes.docx" + , docxTest + "blockquotes" + def + "docx/block_quotes_parse_indent.native" + "docx/golden/block_quotes.docx" + , docxTest + "tables" + def + "docx/tables.native" + "docx/golden/tables.docx" + , docxTest + "tables with lists in cells" + def + "docx/table_with_list_cell.native" + "docx/golden/table_with_list_cell.docx" + , docxTest + "tables with one row" + def + "docx/table_one_row.native" + "docx/golden/table_one_row.docx" + , docxTest + "code block" + def + "docx/codeblock.native" + "docx/golden/codeblock.docx" + ] + , testGroup "track changes" + [ docxTest + "insertion" + def + "docx/track_changes_insertion_all.native" + "docx/golden/track_changes_insertion.docx" + , docxTest + "deletion" + def + "docx/track_changes_deletion_all.native" + "docx/golden/track_changes_deletion.docx" + , docxTest + "move text" + def + "docx/track_changes_move_all.native" + "docx/golden/track_changes_move.docx" + , docxTest + "comments" + def + "docx/comments.native" + "docx/golden/comments.docx" + ] + , testGroup "custom styles" + [ docxTest "custom styles without reference.docx" + def + "docx/custom_style.native" + "docx/golden/custom_style_no_reference.docx" + , docxTest "custom styles with reference.docx" + def{writerReferenceDoc = Just "docx/custom-style-reference.docx"} + "docx/custom_style.native" + "docx/golden/custom_style_reference.docx" + ] + ] diff --git a/test/Tests/Writers/FB2.hs.orig b/test/Tests/Writers/FB2.hs.orig new file mode 100644 index 000000000..6663c42f8 --- /dev/null +++ b/test/Tests/Writers/FB2.hs.orig @@ -0,0 +1,34 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.FB2 (tests) where + +import Test.Tasty +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder + +fb2 :: String -> String +fb2 x = "\n" ++ + "unrecognisedpandoc<p />
" ++ x ++ "
" + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> TestTree +(=:) = test (purely (writeFB2 def) . toPandoc) + +tests :: [TestTree] +tests = [ testGroup "block elements" + ["para" =: para "Lorem ipsum cetera." + =?> fb2 "

Lorem ipsum cetera.

" + ] + , testGroup "inlines" + [ + "Emphasis" =: emph "emphasized" + =?> fb2 "emphasized" + ] + , "bullet list" =: bulletList [ plain $ text "first" + , plain $ text "second" + , plain $ text "third" + ] + =?> fb2 "

\x2022 first

\x2022 second

\x2022 third

" + ] diff --git a/test/Tests/Writers/HTML.hs.orig b/test/Tests/Writers/HTML.hs.orig new file mode 100644 index 000000000..23ff718d3 --- /dev/null +++ b/test/Tests/Writers/HTML.hs.orig @@ -0,0 +1,44 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.HTML (tests) where + +import Data.Text (unpack) +import Test.Tasty +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder + +html :: (ToPandoc a) => a -> String +html = unpack . purely (writeHtml4String def{ writerWrapText = WrapNone }) . toPandoc + +{- + "my test" =: X =?> Y + +is shorthand for + + test html "my test" $ X =?> Y + +which is in turn shorthand for + + test html "my test" (X,Y) +-} + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> TestTree +(=:) = test html + +tests :: [TestTree] +tests = [ testGroup "inline code" + [ "basic" =: code "@&" =?> "@&" + , "haskell" =: codeWith ("",["haskell"],[]) ">>=" + =?> ">>=" + , "nolanguage" =: codeWith ("",["nolanguage"],[]) ">>=" + =?> ">>=" + ] + , testGroup "images" + [ "alt with formatting" =: + image "/url" "title" ("my " <> emph "image") + =?> "\"my" + ] + ] diff --git a/test/Tests/Writers/JATS.hs.orig b/test/Tests/Writers/JATS.hs.orig new file mode 100644 index 000000000..723c0e8a8 --- /dev/null +++ b/test/Tests/Writers/JATS.hs.orig @@ -0,0 +1,108 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.JATS (tests) where + +import Data.Text (unpack) +import Test.Tasty +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder + +jats :: (ToPandoc a) => a -> String +jats = unpack . purely (writeJATS def{ writerWrapText = WrapNone }) . toPandoc + +{- + "my test" =: X =?> Y + +is shorthand for + + test jats "my test" $ X =?> Y + +which is in turn shorthand for + + test jats "my test" (X,Y) +-} + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> TestTree +(=:) = test jats + +tests :: [TestTree] +tests = [ testGroup "inline code" + [ "basic" =: code "@&" =?> "

@&

" + , "lang" =: codeWith ("", ["c"], []) "@&" =?> "

@&

" + ] + , testGroup "block code" + [ "basic" =: codeBlock "@&" =?> "@&" + , "lang" =: codeBlockWith ("", ["c"], []) "@&" =?> "@&" + ] + , testGroup "images" + [ "basic" =: + image "/url" "title" mempty + =?> "" + ] + , testGroup "inlines" + [ "Emphasis" =: emph "emphasized" + =?> "

emphasized

" + ] + , "bullet list" =: bulletList [ plain $ text "first" + , plain $ text "second" + , plain $ text "third" + ] + =?> "\n\ + \ \n\ + \

first

\n\ + \
\n\ + \ \n\ + \

second

\n\ + \
\n\ + \ \n\ + \

third

\n\ + \
\n\ + \
" + , testGroup "definition lists" + [ "with internal link" =: definitionList [(link "#go" "" (str "testing"), + [plain (text "hi there")])] =?> + "\n\ + \ \n\ + \ testing\n\ + \ \n\ + \

hi there

\n\ + \
\n\ + \
\n\ + \
" + ] + , testGroup "math" + [ "escape |" =: para (math "\\sigma|_{\\{x\\}}") =?> + "

\n\ + \\n\ + \σ|{x}

" + ] + , testGroup "headers" + [ "unnumbered header" =: + headerWith ("foo",["unnumbered"],[]) 1 + (text "Header 1" <> note (plain $ text "note")) =?> + "\n\ + \ Header 1<fn>\n\ + \ <p>note</p>\n\ + \ </fn>\n\ + \" + , "unnumbered sub header" =: + headerWith ("foo",["unnumbered"],[]) 1 + (text "Header") + <> headerWith ("foo",["unnumbered"],[]) 2 + (text "Sub-Header") =?> + "\n\ + \ Header\n\ + \ \n\ + \ Sub-Header\n\ + \ \n\ + \" + , "containing image" =: + header 1 (image "imgs/foo.jpg" "" (text "Alt text")) =?> + "\n\ + \ <inline-graphic mimetype=\"image\" mime-subtype=\"jpeg\" xlink:href=\"imgs/foo.jpg\" />\n\ + \" + ] + ] diff --git a/test/Tests/Writers/LaTeX.hs.orig b/test/Tests/Writers/LaTeX.hs.orig new file mode 100644 index 000000000..471d9d9e7 --- /dev/null +++ b/test/Tests/Writers/LaTeX.hs.orig @@ -0,0 +1,176 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.LaTeX (tests) where + +import Data.Text (unpack) +import Test.Tasty +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder + +latex :: (ToPandoc a) => a -> String +latex = latexWithOpts def + +latexListing :: (ToPandoc a) => a -> String +latexListing = latexWithOpts def{ writerListings = True } + +latexWithOpts :: (ToPandoc a) => WriterOptions -> a -> String +latexWithOpts opts = unpack . purely (writeLaTeX opts) . toPandoc + +beamerWithOpts :: (ToPandoc a) => WriterOptions -> a -> String +beamerWithOpts opts = unpack . purely (writeBeamer opts) . 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) -> TestTree +(=:) = test latex + +tests :: [TestTree] +tests = [ testGroup "code blocks" + [ "in footnotes" =: note (para "hi" <> codeBlock "hi") =?> + "\\footnote{hi\n\n\\begin{Verbatim}\nhi\n\\end{Verbatim}\n}" + , 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) + ] + , testGroup "definition lists" + [ "with internal link" =: definitionList [(link "#go" "" (str "testing"), + [plain (text "hi there")])] =?> + "\\begin{description}\n\\tightlist\n\\item[{\\protect\\hyperlink{go}{testing}}]\nhi there\n\\end{description}" + ] + , testGroup "math" + [ "escape |" =: para (math "\\sigma|_{\\{x\\}}") =?> + "\\(\\sigma|_{\\{x\\}}\\)" + ] + , testGroup "headers" + [ "unnumbered header" =: + headerWith ("foo",["unnumbered"],[]) 1 + (text "Header 1" <> note (plain $ text "note")) =?> + "\\hypertarget{foo}{%\n\\section*{\\texorpdfstring{Header 1\\footnote{note}}{Header 1}}\\label{foo}}\n\\addcontentsline{toc}{section}{Header 1}\n" + , "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}" + , "containing image" =: + header 1 (image "imgs/foo.jpg" "" (text "Alt text")) =?> + "\\section{\\texorpdfstring{\\protect\\includegraphics{imgs/foo.jpg}}{Alt text}}" + ] + , 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}" + , "single quotes" =: + code "dog's" =?> "\\texttt{dog\\textquotesingle{}s}" + , "backtick" =: + code "`nu?`" =?> "\\texttt{\\textasciigrave{}nu?\\textasciigrave{}}" + ] + , testGroup "writer options" + [ testGroup "top-level division" $ + let + headers = header 1 (text "header1") + <> header 2 (text "header2") + <> header 3 (text "header3") + + latexTopLevelDiv :: (ToPandoc a) => TopLevelDivision -> a -> String + latexTopLevelDiv division = + latexWithOpts def{ writerTopLevelDivision = division } + + beamerTopLevelDiv :: (ToPandoc a) + => TopLevelDivision -> a -> String + beamerTopLevelDiv division = + beamerWithOpts def { writerTopLevelDivision = division } + in + [ test (latexTopLevelDiv TopLevelSection) + "sections as top-level" $ headers =?> + unlines [ "\\section{header1}\n" + , "\\subsection{header2}\n" + , "\\subsubsection{header3}" + ] + , test (latexTopLevelDiv TopLevelChapter) + "chapters as top-level" $ headers =?> + unlines [ "\\chapter{header1}\n" + , "\\section{header2}\n" + , "\\subsection{header3}" + ] + , test (latexTopLevelDiv TopLevelPart) + "parts as top-level" $ headers =?> + unlines [ "\\part{header1}\n" + , "\\chapter{header2}\n" + , "\\section{header3}" + ] + , test (latexTopLevelDiv TopLevelDefault) + "default top-level" $ headers =?> + unlines [ "\\section{header1}\n" + , "\\subsection{header2}\n" + , "\\subsubsection{header3}" + ] + , test (beamerTopLevelDiv TopLevelSection) + "sections as top-level in beamer" $ headers =?> + unlines [ "\\section{header1}\n" + , "\\subsection{header2}\n" + , "\\subsubsection{header3}" + ] + , test (beamerTopLevelDiv TopLevelChapter) + "chapters are as part in beamer" $ headers =?> + unlines [ "\\part{header1}\n" + , "\\section{header2}\n" + , "\\subsection{header3}" + ] + , test (beamerTopLevelDiv TopLevelPart) + "parts as top-level in beamer" $ headers =?> + unlines [ "\\part{header1}\n" + , "\\section{header2}\n" + , "\\subsection{header3}" + ] + , test (beamerTopLevelDiv TopLevelDefault) + "default top-level in beamer" $ headers =?> + unlines [ "\\section{header1}\n" + , "\\subsection{header2}\n" + , "\\subsubsection{header3}" + ] + , test (latexTopLevelDiv TopLevelPart) + "part top-level, section not in toc" $ + ( headerWith ("", ["unnumbered"], []) 1 (text "header1") + <> headerWith ("", ["unnumbered"], []) 2 (text "header2") + <> headerWith ("", ["unnumbered"], []) 3 (text "header3") + <> headerWith ("", ["unnumbered"], []) 4 (text "header4") + <> headerWith ("", ["unnumbered"], []) 5 (text "header5") + <> headerWith ("", ["unnumbered"], []) 6 (text "header6")) + =?> + unlines [ "\\part*{header1}" + , "\\addcontentsline{toc}{part}{header1}\n" + , "\\chapter*{header2}" + , "\\addcontentsline{toc}{chapter}{header2}\n" + , "\\section*{header3}" + , "\\addcontentsline{toc}{section}{header3}\n" + , "\\subsection*{header4}" + , "\\addcontentsline{toc}{subsection}{header4}\n" + , "\\subsubsection*{header5}" + , "\\addcontentsline{toc}{subsubsection}{header5}\n" + , "\\paragraph{header6}" + , "\\addcontentsline{toc}{paragraph}{header6}" + ] + ] + ] + ] diff --git a/test/Tests/Writers/Markdown.hs.orig b/test/Tests/Writers/Markdown.hs.orig new file mode 100644 index 000000000..7f9ac3627 --- /dev/null +++ b/test/Tests/Writers/Markdown.hs.orig @@ -0,0 +1,267 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# OPTIONS_GHC -fno-warn-name-shadowing #-} +module Tests.Writers.Markdown (tests) where + +import Data.Text (unpack) +import Test.Tasty +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder + +defopts :: WriterOptions +defopts = def{ writerExtensions = pandocExtensions } + +markdown :: (ToPandoc a) => a -> String +markdown = unpack . purely (writeMarkdown defopts) . toPandoc + +markdownWithOpts :: (ToPandoc a) => WriterOptions -> a -> String +markdownWithOpts opts x = unpack . purely (writeMarkdown opts) $ toPandoc x + +{- + "my test" =: X =?> Y + +is shorthand for + + test markdown "my test" $ X =?> Y + +which is in turn shorthand for + + test markdown "my test" (X,Y) +-} + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> TestTree +(=:) = test markdown + +tests :: [TestTree] +tests = [ "indented code after list" + =: (orderedList [ para "one" <> para "two" ] <> codeBlock "test") + =?> "1. one\n\n two\n\n\n\n test" + , "list with tight sublist" + =: bulletList [ plain "foo" <> bulletList [ plain "bar" ], + plain "baz" ] + =?> "- foo\n - bar\n- baz\n" + ] ++ [noteTests] ++ [shortcutLinkRefsTests] + +{- + +Testing with the following text: + +First Header +============ + +This is a footnote.[^1] And this is a [link](https://www.google.com). + +> A note inside a block quote.[^2] +> +> A second paragraph. + +Second Header +============= + +Some more text. + + +[^1]: Down here. + +[^2]: The second note. + +-} + +noteTestDoc :: Blocks +noteTestDoc = + header 1 "First Header" <> + para ("This is a footnote." <> + note (para "Down here.") <> + " And this is a " <> + link "https://www.google.com" "" "link" <> + ".") <> + blockQuote (para ("A note inside a block quote." <> + note (para "The second note.")) <> + para "A second paragraph.") <> + header 1 "Second Header" <> + para "Some more text." + + + +noteTests :: TestTree +noteTests = testGroup "note and reference location" + [ test (markdownWithOpts defopts) + "footnotes at the end of a document" $ + noteTestDoc =?> + (unlines [ "First Header" + , "============" + , "" + , "This is a footnote.[^1] And this is a [link](https://www.google.com)." + , "" + , "> A note inside a block quote.[^2]" + , ">" + , "> A second paragraph." + , "" + , "Second Header" + , "=============" + , "" + , "Some more text." + , "" + , "[^1]: Down here." + , "" + , "[^2]: The second note." + ]) + , test (markdownWithOpts defopts{writerReferenceLocation=EndOfBlock}) + "footnotes at the end of blocks" $ + noteTestDoc =?> + (unlines [ "First Header" + , "============" + , "" + , "This is a footnote.[^1] And this is a [link](https://www.google.com)." + , "" + , "[^1]: Down here." + , "" + , "> A note inside a block quote.[^2]" + , ">" + , "> A second paragraph." + , "" + , "[^2]: The second note." + , "" + , "Second Header" + , "=============" + , "" + , "Some more text." + ]) + , test (markdownWithOpts defopts{writerReferenceLocation=EndOfBlock, writerReferenceLinks=True}) + "footnotes and reference links at the end of blocks" $ + noteTestDoc =?> + (unlines [ "First Header" + , "============" + , "" + , "This is a footnote.[^1] And this is a [link]." + , "" + , "[^1]: Down here." + , "" + , " [link]: https://www.google.com" + , "" + , "> A note inside a block quote.[^2]" + , ">" + , "> A second paragraph." + , "" + , "[^2]: The second note." + , "" + , "Second Header" + , "=============" + , "" + , "Some more text." + ]) + , test (markdownWithOpts defopts{writerReferenceLocation=EndOfSection}) + "footnotes at the end of section" $ + noteTestDoc =?> + (unlines [ "First Header" + , "============" + , "" + , "This is a footnote.[^1] And this is a [link](https://www.google.com)." + , "" + , "> A note inside a block quote.[^2]" + , ">" + , "> A second paragraph." + , "" + , "[^1]: Down here." + , "" + , "[^2]: The second note." + , "" + , "Second Header" + , "=============" + , "" + , "Some more text." + ]) + + ] + +shortcutLinkRefsTests :: TestTree +shortcutLinkRefsTests = + let infix 4 =: + (=:) :: (ToString a, ToPandoc a) + + => String -> (a, String) -> TestTree + (=:) = test (purely (writeMarkdown defopts{writerReferenceLinks = True}) . toPandoc) + in testGroup "Shortcut reference links" + [ "Simple link (shortcutable)" + =: para (link "/url" "title" "foo") + =?> "[foo]\n\n [foo]: /url \"title\"" + , "Followed by another link (unshortcutable)" + =: para ((link "/url1" "title1" "first") + <> (link "/url2" "title2" "second")) + =?> unlines [ "[first][][second]" + , "" + , " [first]: /url1 \"title1\"" + , " [second]: /url2 \"title2\"" + ] + , "Followed by space and another link (unshortcutable)" + =: para ((link "/url1" "title1" "first") <> " " + <> (link "/url2" "title2" "second")) + =?> unlines [ "[first][] [second]" + , "" + , " [first]: /url1 \"title1\"" + , " [second]: /url2 \"title2\"" + ] + , "Reference link is used multiple times (unshortcutable)" + =: para ((link "/url1" "" "foo") <> (link "/url2" "" "foo") + <> (link "/url3" "" "foo")) + =?> unlines [ "[foo][][foo][1][foo][2]" + , "" + , " [foo]: /url1" + , " [1]: /url2" + , " [2]: /url3" + ] + , "Reference link is used multiple times (unshortcutable)" + =: para ((link "/url1" "" "foo") <> " " <> (link "/url2" "" "foo") + <> " " <> (link "/url3" "" "foo")) + =?> unlines [ "[foo][] [foo][1] [foo][2]" + , "" + , " [foo]: /url1" + , " [1]: /url2" + , " [2]: /url3" + ] + , "Reference link is followed by text in brackets" + =: para ((link "/url" "" "link") <> "[text in brackets]") + =?> unlines [ "[link][]\\[text in brackets\\]" + , "" + , " [link]: /url" + ] + , "Reference link is followed by space and text in brackets" + =: para ((link "/url" "" "link") <> " [text in brackets]") + =?> unlines [ "[link][] \\[text in brackets\\]" + , "" + , " [link]: /url" + ] + , "Reference link is followed by RawInline" + =: para ((link "/url" "" "link") <> rawInline "markdown" "[rawText]") + =?> unlines [ "[link][][rawText]" + , "" + , " [link]: /url" + ] + , "Reference link is followed by space and RawInline" + =: para ((link "/url" "" "link") <> space <> rawInline "markdown" "[rawText]") + =?> unlines [ "[link][] [rawText]" + , "" + , " [link]: /url" + ] + , "Reference link is followed by RawInline with space" + =: para ((link "/url" "" "link") <> rawInline "markdown" " [rawText]") + =?> unlines [ "[link][] [rawText]" + , "" + , " [link]: /url" + ] + , "Reference link is followed by citation" + =: para ((link "/url" "" "link") <> cite [Citation "author" [] [] NormalCitation 0 0] (str "[@author]")) + =?> unlines [ "[link][][@author]" + , "" + , " [link]: /url" + ] + , "Reference link is followed by space and citation" + =: para ((link "/url" "" "link") <> space <> cite [Citation "author" [] [] NormalCitation 0 0] (str "[@author]")) + =?> unlines [ "[link][] [@author]" + , "" + , " [link]: /url" + ] + ] diff --git a/test/Tests/Writers/Muse.hs.orig b/test/Tests/Writers/Muse.hs.orig new file mode 100644 index 000000000..b86dee5e1 --- /dev/null +++ b/test/Tests/Writers/Muse.hs.orig @@ -0,0 +1,410 @@ +module Tests.Writers.Muse (tests) where + +import Data.Text (unpack) +import Test.Tasty +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder + +muse :: (ToPandoc a) => a -> String +muse = museWithOpts def{ writerWrapText = WrapNone, + writerExtensions = extensionsFromList [Ext_amuse, + Ext_auto_identifiers] } + +museWithOpts :: (ToPandoc a) => WriterOptions -> a -> String +museWithOpts opts = unpack . purely (writeMuse opts) . toPandoc + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> TestTree +(=:) = test muse + +tests :: [TestTree] +tests = [ testGroup "block elements" + [ "plain" =: plain (text "Foo bar.") =?> "Foo bar." + , testGroup "paragraphs" + [ "single paragraph" =: para (text "Sample paragraph.") + =?> "Sample paragraph." + , "two paragraphs" =: para (text "First paragraph.") <> + para (text "Second paragraph.") + =?> unlines [ "First paragraph." + , "" + , "Second paragraph." + ] + ] + , "line block" =: lineBlock [text "Foo", text "bar", text "baz"] + =?> unlines [ "> Foo" + , "> bar" + , "> baz" + ] + , "code block" =: codeBlock "int main(void) {\n\treturn 0;\n}" + =?> unlines [ "" + , "int main(void) {" + , "\treturn 0;" + , "}" + , "" + ] + , "html raw block" =: rawBlock "html" "
" + =?> unlines [ "" + , "
" + , "
" + ] + , "block quote" =: blockQuote (para (text "Foo")) + =?> unlines [ "" + , "Foo" + , "" + ] + , testGroup "lists" + [ testGroup "simple lists" + [ + "ordered list" =: orderedList [ plain $ text "first" + , plain $ text "second" + , plain $ text "third" + ] + =?> unlines [ " 1. first" + , " 2. second" + , " 3. third" + ] + , "ordered list with Roman numerals" + =: orderedListWith (1, UpperRoman, DefaultDelim) + [ plain $ text "first" + , plain $ text "second" + , plain $ text "third" + ] + =?> unlines [ " I. first" + , " II. second" + , " III. third" + ] + , "bullet list" =: bulletList [ plain $ text "first" + , plain $ text "second" + , plain $ text "third" + ] + =?> unlines [ " - first" + , " - second" + , " - third" + ] + , "definition list" =: definitionList [ (text "first definition", [plain $ text "first description"]) + , (text "second definition", [plain $ text "second description"]) + , (text "third definition", [plain $ text "third description"]) + ] + =?> unlines [ " first definition :: first description" + , " second definition :: second description" + , " third definition :: third description" + ] + , "definition list with multiple descriptions" =: + definitionList [ (text "first definition", [plain $ text "first description" + ,plain $ text "second description"]) + , (text "second definition", [plain $ text "third description"]) + ] + =?> unlines [ " first definition :: first description" + , " :: second description" + , " second definition :: third description" + ] + , "definition list with empty term" =: + definitionList [ (text "first definition", [plain $ text "first description"]) + , (mempty, [plain $ text "second description"]) + , (str "", [plain $ text "third description"]) + ] + =?> unlines [ " first definition :: first description" + , " :: second description" + , " :: third description" + ] + ] + -- Test that lists of the same type and style are separated with two blanklines + , testGroup "sequential lists" + [ "bullet lists" =: + bulletList [ para $ text "First" + , para $ text "Second" + , para $ text "Third" + ] <> + bulletList [ para $ text "Fourth" + , para $ text "Fifth" + ] =?> + unlines [ " - First" + , " - Second" + , " - Third" + , "" + , "" + , " - Fourth" + , " - Fifth" + ] + , "ordered lists of the same style" =: + orderedListWith (1, UpperRoman, DefaultDelim) [ para $ text "First" + , para $ text "Second" + ] <> + orderedListWith (1, UpperRoman, DefaultDelim) [ para $ text "Third" + , para $ text "Fourth" + ] =?> + unlines [ " I. First" + , " II. Second" + , "" + , "" + , " I. Third" + , " II. Fourth" + ] + , "ordered lists with equal styles" =: + orderedList [ para $ text "First" + , para $ text "Second" + ] <> + orderedListWith (1, Decimal, DefaultDelim) [ para $ text "Third" + , para $ text "Fourth" + ] =?> + unlines [ " 1. First" + , " 2. Second" + , "" + , "" + , " 1. Third" + , " 2. Fourth" + ] + , "bullet and ordered lists" =: + bulletList [ para $ text "First" + , para $ text "Second" + ] <> + orderedListWith (1, UpperRoman, DefaultDelim) [ para $ text "Third" + , para $ text "Fourth" + ] =?> + unlines [ " - First" + , " - Second" + , "" + , " I. Third" + , " II. Fourth" + ] + , "different style ordered lists" =: + orderedListWith (1, UpperRoman, DefaultDelim) [ para $ text "First" + , para $ text "Second" + ] <> + orderedListWith (1, Decimal, DefaultDelim) [ para $ text "Third" + , para $ text "Fourth" + ] =?> + unlines [ " I. First" + , " II. Second" + , "" + , " 1. Third" + , " 2. Fourth" + ] + ] + , testGroup "nested lists" + [ "nested ordered list" =: orderedList [ plain $ text "First outer" + , plain (text "Second outer:") <> + orderedList [ plain $ text "first" + , plain $ text "second" + ] + , plain $ text "Third outer" + ] + =?> unlines [ " 1. First outer" + , " 2. Second outer:" + , " 1. first" + , " 2. second" + , " 3. Third outer" + ] + , "nested bullet lists" =: bulletList [ plain $ text "First outer" + , plain (text "Second outer:") <> + bulletList [ plain $ text "first" + , plain $ text "second" + ] + , plain $ text "Third outer" + ] + =?> unlines [ " - First outer" + , " - Second outer:" + , " - first" + , " - second" + , " - Third outer" + ] + , "nested definition lists" =: definitionList [ (text "first definition", [plain $ text "first description"]) + , (text "second definition", + [ plain (text "second description") <> + definitionList [ ( text "first inner definition" + , [plain $ text "first inner description"]) + , ( text "second inner definition" + , [plain $ text "second inner description"]) + ] + ] + ) + ] + =?> unlines [ " first definition :: first description" + , " second definition :: second description" + , " first inner definition :: first inner description" + , " second inner definition :: second inner description" + ] + ] + -- Check that list is intended with one space even inside a quote + , "List inside block quote" =: blockQuote (orderedList [ plain $ text "first" + , plain $ text "second" + , plain $ text "third" + ]) + =?> unlines [ "" + , " 1. first" + , " 2. second" + , " 3. third" + , "" + ] + ] + , testGroup "headings" + [ "normal heading" =: + header 1 (text "foo") =?> "* foo" + , "heading levels" =: + header 1 (text "First level") <> + header 3 (text "Third level") =?> + unlines [ "* First level" + , "" + , "*** Third level" + ] + , "heading with ID" =: + headerWith ("bar", [], []) 2 (text "Foo") =?> + unlines [ "** Foo" + , "#bar" + ] + ] + , "horizontal rule" =: horizontalRule =?> "----" + , "escape horizontal rule" =: para (text "----") =?> "----" + , "escape nonbreaking space" =: para (text "~~") =?> "~~" + , testGroup "tables" + [ "table without header" =: + let rows = [[para $ text "Para 1.1", para $ text "Para 1.2"] + ,[para $ text "Para 2.1", para $ text "Para 2.2"]] + in simpleTable [] rows + =?> + unlines [ " Para 1.1 | Para 1.2" + , " Para 2.1 | Para 2.2" + ] + , "table with header" =: + let headers = [plain $ text "header 1", plain $ text "header 2"] + rows = [[para $ text "Para 1.1", para $ text "Para 1.2"] + ,[para $ text "Para 2.1", para $ text "Para 2.2"]] + in simpleTable headers rows + =?> + unlines [ " header 1 || header 2" + , " Para 1.1 | Para 1.2" + , " Para 2.1 | Para 2.2" + ] + , "table with header and caption" =: + let caption = text "Table 1" + headers = [plain $ text "header 1", plain $ text "header 2"] + rows = [[para $ text "Para 1.1", para $ text "Para 1.2"] + ,[para $ text "Para 2.1", para $ text "Para 2.2"]] + in table caption mempty headers rows + =?> unlines [ " header 1 || header 2" + , " Para 1.1 | Para 1.2" + , " Para 2.1 | Para 2.2" + , " |+ Table 1 +|" + ] + ] + , "div with bullet list" =: + divWith nullAttr (bulletList [para $ text "foo"]) =?> + unlines [ " - foo" ] -- Making sure bullets are indented + -- Null is trivial + ] + , testGroup "inline elements" + [ testGroup "string" + [ "string" =: str "foo" =?> "foo" + , "escape footnote" =: str "[1]" =?> "[1]" + , "escape verbatim close tag" =: str "foobar" + =?> "foo</verbatim>bar" + , "escape pipe to avoid accidental tables" =: str "foo | bar" + =?> "foo | bar" + , "escape hash to avoid accidental anchors" =: text "#foo bar" + =?> "#foo bar" + , "escape definition list markers" =: str "::" =?> "::" + , "normalize strings before escaping" =: fromList [Str ":", Str ":"] =?> "::" + -- We don't want colons to be escaped if they can't be confused + -- with definition list item markers. + , "do not escape colon" =: str ":" =?> ":" + , "escape - to avoid accidental unordered lists" =: text " - foo" =?> " - foo" + , "escape - inside a list to avoid accidental nested unordered lists" =: + bulletList [ (para $ text "foo") <> + (para $ text "- bar") + ] =?> + unlines [ " - foo" + , "" + , " - bar" + ] + ] + , testGroup "emphasis" + [ "emph" =: emph (text "foo") =?> "foo" + , "strong" =: strong (text "foo") =?> "foo" + , "strikeout" =: strikeout (text "foo") =?> "foo" + ] + , "superscript" =: superscript (text "foo") =?> "foo" + , "subscript" =: subscript (text "foo") =?> "foo" + , "smallcaps" =: smallcaps (text "foo") =?> "foo" + , "smallcaps near emphasis" =: emph (str "foo") <> smallcaps (str "bar") =?> "foobar" + , "single quoted" =: singleQuoted (text "foo") =?> "‘foo’" + , "double quoted" =: doubleQuoted (text "foo") =?> "“foo”" + -- Cite is trivial + , testGroup "code" + [ "simple" =: code "foo" =?> "foo" + , "escape tag" =: code "foo = bar baz" =?> "foo = bar</code> baz" + , "normalization with attributes" =: codeWith ("",["haskell"],[]) "foo" <> code "bar" =?> "foobar" + , "normalization" =: code " code "de>" =?> "</code>" + , "normalization with empty string" =: code " str "" <> code "de>" =?> "</code>" + ] + , testGroup "spaces" + [ "space" =: text "a" <> space <> text "b" =?> "a b" + , "soft break" =: text "a" <> softbreak <> text "b" =?> "a b" + , test (museWithOpts def{ writerWrapText = WrapPreserve }) + "preserve soft break" $ text "a" <> softbreak <> text "b" + =?> "a\nb" + , "line break" =: text "a" <> linebreak <> text "b" =?> "a
\nb" + ] + , testGroup "math" + [ "inline math" =: math "2^3" =?> "23" + , "display math" =: displayMath "2^3" =?> "23" + , "multiple letters in inline math" =: math "abc" =?> "abc" + , "expand math before normalization" =: math "[" <> str "2]" =?> "[2]" + , "multiple math expressions inside one inline list" =: math "5_4" <> text ", " <> displayMath "3^2" =?> "54, 32" + ] + , "raw inline" + =: rawInline "html" "marked text" + =?> "marked text" + , testGroup "links" + [ "link with description" =: link "https://example.com" "" (str "Link 1") + =?> "[[https://example.com][Link 1]]" + , "link without description" =: link "https://example.com" "" (str "https://example.com") + =?> "[[https://example.com]]" + -- Internal links in Muse include '#' + , "link to anchor" =: link "#intro" "" (str "Introduction") + =?> "[[#intro][Introduction]]" + -- According to Emacs Muse manual, links to images should be prefixed with "URL:" + , "link to image with description" =: link "1.png" "" (str "Link to image") + =?> "[[URL:1.png][Link to image]]" + , "link to image without description" =: link "1.png" "" (str "1.png") + =?> "[[URL:1.png]]" + ] + , "image" =: image "image.png" "Image 1" (str "") =?> "[[image.png][Image 1]]" + , "image with width" =: + imageWith ("", [], [("width", "60%")]) "image.png" "Image" (str "") =?> + "[[image.png 60][Image]]" + , "note" =: note (plain (text "Foo")) + =?> unlines [ "[1]" + , "" + , "[1] Foo" + ] + , "span with class" =: spanWith ("",["foobar"],[]) (text "Some text") + =?> "Some text" + , "span with anchor" =: spanWith ("anchor", [], []) (text "Foo bar") + =?> "#anchor Foo bar" + , "span with class and anchor" =: spanWith ("anchor", ["foo"], []) (text "bar") + =?> "#anchor bar" + , testGroup "combined" + [ "emph word before" =: + para (text "foo" <> emph (text "bar")) =?> + "foobar" + , "emph word after" =: + para (emph (text "foo") <> text "bar") =?> + "foobar" + , "emph quoted" =: + para (doubleQuoted (emph (text "foo"))) =?> + "“foo”" + , "strong word before" =: + para (text "foo" <> strong (text "bar")) =?> + "foobar" + , "strong word after" =: + para (strong (text "foo") <> text "bar") =?> + "foobar" + , "strong quoted" =: + para (singleQuoted (strong (text "foo"))) =?> + "‘foo’" + ] + ] + ] diff --git a/test/Tests/Writers/Native.hs.orig b/test/Tests/Writers/Native.hs.orig new file mode 100644 index 000000000..0c4bf7623 --- /dev/null +++ b/test/Tests/Writers/Native.hs.orig @@ -0,0 +1,22 @@ +module Tests.Writers.Native (tests) where + +import Data.Text (unpack) +import Test.Tasty +import Test.Tasty.QuickCheck +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () + +p_write_rt :: Pandoc -> Bool +p_write_rt d = + read (unpack $ purely (writeNative def{ writerTemplate = Just "" }) d) == d + +p_write_blocks_rt :: [Block] -> Bool +p_write_blocks_rt bs = + read (unpack $ purely (writeNative def) (Pandoc nullMeta bs)) == bs + +tests :: [TestTree] +tests = [ testProperty "p_write_rt" p_write_rt + , testProperty "p_write_blocks_rt" $ mapSize + (\x -> if x > 3 then 3 else x) p_write_blocks_rt + ] diff --git a/test/Tests/Writers/OOXML.hs.orig b/test/Tests/Writers/OOXML.hs.orig new file mode 100644 index 000000000..bdfdea145 --- /dev/null +++ b/test/Tests/Writers/OOXML.hs.orig @@ -0,0 +1,184 @@ +{-# LANGUAGE PatternGuards #-} +{-# LANGUAGE OverloadedStrings #-} + +module Tests.Writers.OOXML (ooxmlTest) where + +import Text.Pandoc +import Test.Tasty +import Test.Tasty.Golden.Advanced +import Codec.Archive.Zip +import Text.XML.Light +import qualified Data.ByteString as BS +import qualified Data.ByteString.Lazy as BL +import qualified Data.Text.IO as T +import Data.List (isSuffixOf, sort, (\\), intercalate, union) +import Data.Maybe (catMaybes, mapMaybe) +import Tests.Helpers +import Data.Algorithm.Diff +import System.FilePath.Glob (compile, match) + +compareXMLBool :: Content -> Content -> Bool +-- We make a special exception for times at the moment, and just pass +-- them because we can't control the utctime when running IO. Besides, +-- so long as we have two times, we're okay. +compareXMLBool (Elem myElem) (Elem goodElem) + | (QName "created" _ (Just "dcterms")) <- elName myElem + , (QName "created" _ (Just "dcterms")) <- elName goodElem = + True +compareXMLBool (Elem myElem) (Elem goodElem) + | (QName "modified" _ (Just "dcterms")) <- elName myElem + , (QName "modified" _ (Just "dcterms")) <- elName goodElem = + True +compareXMLBool (Elem myElem) (Elem goodElem) = + elName myElem == elName goodElem && + elAttribs myElem == elAttribs goodElem && + and (zipWith compareXMLBool (elContent myElem) (elContent goodElem)) +compareXMLBool (Text myCData) (Text goodCData) = + cdVerbatim myCData == cdVerbatim goodCData && + cdData myCData == cdData goodCData && + cdLine myCData == cdLine goodCData +compareXMLBool (CRef myStr) (CRef goodStr) = + myStr == goodStr +compareXMLBool _ _ = False + +displayDiff :: Content -> Content -> String +displayDiff elemA elemB = + showDiff (1,1) $ getDiff (lines $ ppContent elemA) (lines $ ppContent elemB) + +goldenArchive :: FilePath -> IO Archive +goldenArchive fp = (toArchive . BL.fromStrict) <$> BS.readFile fp + +testArchive :: (WriterOptions -> Pandoc -> PandocIO BL.ByteString) + -> WriterOptions + -> FilePath + -> IO Archive +testArchive writerFn opts fp = do + txt <- T.readFile fp + bs <- runIOorExplode $ readNative def txt >>= writerFn opts + return $ toArchive bs + +compareFileList :: FilePath -> Archive -> Archive -> Maybe String +compareFileList goldenFP goldenArch testArch = + let testFiles = filesInArchive testArch + goldenFiles = filesInArchive goldenArch + diffTestGolden = testFiles \\ goldenFiles + diffGoldenTest = goldenFiles \\ testFiles + + results = + [ if null diffGoldenTest + then Nothing + else Just $ + "Files in " ++ goldenFP ++ " but not in generated archive:\n" ++ + intercalate ", " diffGoldenTest + , if null diffTestGolden + then Nothing + else Just $ + "Files in generated archive but not in " ++ goldenFP ++ ":\n" ++ + intercalate ", " diffTestGolden + ] + in + if null $ catMaybes results + then Nothing + else Just $ intercalate "\n" $ catMaybes results + +compareXMLFile' :: FilePath -> Archive -> Archive -> Either String () +compareXMLFile' fp goldenArch testArch = do + testEntry <- case findEntryByPath fp testArch of + Just entry -> Right entry + Nothing -> Left $ + "Can't extract " ++ fp ++ " from generated archive" + testXMLDoc <- case parseXMLDoc $ fromEntry testEntry of + Just doc -> Right doc + Nothing -> Left $ + "Can't parse xml in " ++ fp ++ " from generated archive" + + goldenEntry <- case findEntryByPath fp goldenArch of + Just entry -> Right entry + Nothing -> Left $ + "Can't extract " ++ fp ++ " from archive in stored file" + goldenXMLDoc <- case parseXMLDoc $ fromEntry goldenEntry of + Just doc -> Right doc + Nothing -> Left $ + "Can't parse xml in " ++ fp ++ " from archive in stored file" + + let testContent = Elem testXMLDoc + goldenContent = Elem goldenXMLDoc + + if compareXMLBool goldenContent testContent + then Right () + else Left $ + "Non-matching xml in " ++ fp ++ ":\n" ++ displayDiff testContent goldenContent + +compareXMLFile :: FilePath -> Archive -> Archive -> Maybe String +compareXMLFile fp goldenArch testArch = + case compareXMLFile' fp goldenArch testArch of + Right _ -> Nothing + Left s -> Just s + +compareAllXMLFiles :: Archive -> Archive -> Maybe String +compareAllXMLFiles goldenArch testArch = + let allFiles = filesInArchive goldenArch `union` filesInArchive testArch + allXMLFiles = sort $ + filter + (\fp -> ".xml" `isSuffixOf` fp || ".rels" `isSuffixOf` fp) + allFiles + results = + mapMaybe (\fp -> compareXMLFile fp goldenArch testArch) allXMLFiles + in + if null results + then Nothing + else Just $ unlines results + +compareMediaFile' :: FilePath -> Archive -> Archive -> Either String () +compareMediaFile' fp goldenArch testArch = do + testEntry <- case findEntryByPath fp testArch of + Just entry -> Right entry + Nothing -> Left $ + "Can't extract " ++ fp ++ " from generated archive" + goldenEntry <- case findEntryByPath fp goldenArch of + Just entry -> Right entry + Nothing -> Left $ + "Can't extract " ++ fp ++ " from archive in stored file" + + if fromEntry testEntry == fromEntry goldenEntry + then Right () + else Left $ + "Non-matching binary file: " ++ fp + +compareMediaFile :: FilePath -> Archive -> Archive -> Maybe String +compareMediaFile fp goldenArch testArch = + case compareMediaFile' fp goldenArch testArch of + Right _ -> Nothing + Left s -> Just s + +compareAllMediaFiles :: Archive -> Archive -> Maybe String +compareAllMediaFiles goldenArch testArch = + let allFiles = filesInArchive goldenArch `union` filesInArchive testArch + mediaPattern = compile "*/media/*" + allMediaFiles = sort $ + filter (match mediaPattern) allFiles + results = + mapMaybe (\fp -> compareMediaFile fp goldenArch testArch) allMediaFiles + in + if null results + then Nothing + else Just $ unlines results + +ooxmlTest :: (WriterOptions -> Pandoc -> PandocIO BL.ByteString) + -> String + -> WriterOptions + -> FilePath + -> FilePath + -> TestTree +ooxmlTest writerFn testName opts nativeFP goldenFP = + goldenTest + testName + (goldenArchive goldenFP) + (testArchive writerFn opts nativeFP) + (\goldenArch testArch -> + let res = catMaybes [ compareFileList goldenFP goldenArch testArch + , compareAllXMLFiles goldenArch testArch + , compareAllMediaFiles goldenArch testArch + ] + in return $ if null res then Nothing else Just $ unlines res) + (\a -> BL.writeFile goldenFP $ fromArchive a) diff --git a/test/Tests/Writers/Org.hs.orig b/test/Tests/Writers/Org.hs.orig new file mode 100644 index 000000000..9cbe360da --- /dev/null +++ b/test/Tests/Writers/Org.hs.orig @@ -0,0 +1,25 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.Org (tests) where + +import Test.Tasty +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> TestTree +(=:) = test (purely (writeOrg def . toPandoc)) + +tests :: [TestTree] +tests = [ testGroup "links" + -- See http://orgmode.org/manual/Internal-links.html#Internal-links + [ "simple link" + =: link "/url" "" "foo" + =?> "[[/url][foo]]" + , "internal link to anchor" + =: link "#my-custom-id" "" "#my-custom-id" + =?> "[[#my-custom-id]]" + ] + ] diff --git a/test/Tests/Writers/Plain.hs.orig b/test/Tests/Writers/Plain.hs.orig new file mode 100644 index 000000000..ab09bca26 --- /dev/null +++ b/test/Tests/Writers/Plain.hs.orig @@ -0,0 +1,21 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.Plain (tests) where + +import Test.Tasty +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder + + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> TestTree +(=:) = test (purely (writePlain def) . toPandoc) + + +tests :: [TestTree] +tests = [ "strongly emphasized text to uppercase" + =: strong "Straße" + =?> "STRASSE" + ] diff --git a/test/Tests/Writers/Powerpoint.hs.orig b/test/Tests/Writers/Powerpoint.hs.orig new file mode 100644 index 000000000..9af8fc471 --- /dev/null +++ b/test/Tests/Writers/Powerpoint.hs.orig @@ -0,0 +1,93 @@ +module Tests.Writers.Powerpoint (tests) where + +import Tests.Writers.OOXML (ooxmlTest) +import Text.Pandoc +import Test.Tasty +import System.FilePath + +-- templating is important enough, and can break enough things, that +-- we want to run all our tests with both default formatting and a +-- template. + +modifyPptxName :: FilePath -> FilePath +modifyPptxName fp = + addExtension (dropExtension fp ++ "_templated") "pptx" + +pptxTests :: String -> WriterOptions -> FilePath -> FilePath -> (TestTree, TestTree) +pptxTests name opts native pptx = + let referenceDoc = "pptx/reference_depth.pptx" + in + ( ooxmlTest + writePowerpoint + name + opts{writerReferenceDoc=Nothing} + native + pptx + , ooxmlTest + writePowerpoint + name + opts{writerReferenceDoc=Just referenceDoc} + native + (modifyPptxName pptx) + ) + +groupPptxTests :: [(TestTree, TestTree)] -> [TestTree] +groupPptxTests pairs = + let (noRefs, refs) = unzip pairs + in + [ testGroup "Default slide formatting" noRefs + , testGroup "With `--reference-doc` pptx file" refs + ] + + +tests :: [TestTree] +tests = groupPptxTests [ pptxTests "Inline formatting" + def + "pptx/inline_formatting.native" + "pptx/inline_formatting.pptx" + , pptxTests "Slide breaks (default slide-level)" + def + "pptx/slide_breaks.native" + "pptx/slide_breaks.pptx" + , pptxTests "slide breaks (slide-level set to 1)" + def{ writerSlideLevel = Just 1 } + "pptx/slide_breaks.native" + "pptx/slide_breaks_slide_level_1.pptx" + , pptxTests "lists" + def + "pptx/lists.native" + "pptx/lists.pptx" + , pptxTests "tables" + def + "pptx/tables.native" + "pptx/tables.pptx" + , pptxTests "table of contents" + def{ writerTableOfContents = True } + "pptx/slide_breaks.native" + "pptx/slide_breaks_toc.pptx" + , pptxTests "end notes" + def + "pptx/endnotes.native" + "pptx/endnotes.pptx" + , pptxTests "end notes, with table of contents" + def { writerTableOfContents = True } + "pptx/endnotes.native" + "pptx/endnotes_toc.pptx" + , pptxTests "images" + def + "pptx/images.native" + "pptx/images.pptx" + , pptxTests "two-column layout" + def + "pptx/two_column.native" + "pptx/two_column.pptx" + , pptxTests "speaker notes" + def + "pptx/speaker_notes.native" + "pptx/speaker_notes.pptx" + , pptxTests "remove empty slides" + def + "pptx/remove_empty_slides.native" + "pptx/remove_empty_slides.pptx" + + ] diff --git a/test/Tests/Writers/RST.hs.orig b/test/Tests/Writers/RST.hs.orig new file mode 100644 index 000000000..e54ce4737 --- /dev/null +++ b/test/Tests/Writers/RST.hs.orig @@ -0,0 +1,130 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.RST (tests) where + +import Test.Tasty +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> TestTree +(=:) = test (purely (writeRST def . toPandoc)) + +tests :: [TestTree] +tests = [ testGroup "rubrics" + [ "in list item" =: + bulletList [header 2 (text "foo")] =?> + "- .. rubric:: foo" + , "in definition list item" =: + definitionList [(text "foo", [header 2 (text "bar"), + para $ text "baz"])] =?> + unlines + [ "foo" + , " .. rubric:: bar" + , "" + , " baz"] + , "in block quote" =: + blockQuote (header 1 (text "bar")) =?> + " .. rubric:: bar" + , "with id" =: + blockQuote (headerWith ("foo",[],[]) 1 (text "bar")) =?> + unlines + [ " .. rubric:: bar" + , " :name: foo"] + , "with id class" =: + blockQuote (headerWith ("foo",["baz"],[]) 1 (text "bar")) =?> + unlines + [ " .. rubric:: bar" + , " :name: foo" + , " :class: baz"] + ] + , testGroup "ligatures" -- handling specific sequences of blocks + [ "a list is closed by a comment before a quote" =: -- issue 4248 + bulletList [plain "bulleted"] <> blockQuote (plain "quoted") =?> + unlines + [ "- bulleted" + , "" + , ".." + , "" + , " quoted"] + ] + , testGroup "inlines" + [ "are removed when empty" =: -- #4434 + plain (strong (str "")) =?> "" + , "do not cause the introduction of extra spaces when removed" =: + plain (strong (str "") <> emph (str "text")) =?> "*text*" + , "spaces are stripped at beginning and end" =: + -- pandoc issue 4327 "The text within inline markup may not + -- begin or end with whitespace" + -- http://docutils.sourceforge.net/docs/ref/rst/restructuredtext.html#inline-markup + strong (space <> str "text" <> space <> space) =?> "**text**" + , "single space stripped" =: + strong space =?> "" + ] + , testGroup "headings" + [ "normal heading" =: + header 1 (text "foo") =?> + unlines + [ "foo" + , "==="] + -- note: heading normalization is only done in standalone mode + , test (purely (writeRST def{ writerTemplate = Just "$body$\n" }) . toPandoc) + "heading levels" $ + header 1 (text "Header 1") <> + header 3 (text "Header 2") <> + header 2 (text "Header 2") <> + header 1 (text "Header 1") <> + header 4 (text "Header 2") <> + header 5 (text "Header 3") <> + header 3 (text "Header 2") =?> + unlines + [ "Header 1" + , "========" + , "" + , "Header 2" + , "--------" + , "" + , "Header 2" + , "--------" + , "" + , "Header 1" + , "========" + , "" + , "Header 2" + , "--------" + , "" + , "Header 3" + , "~~~~~~~~" + , "" + , "Header 2" + , "--------"] + , test (purely (writeRST def{ writerTemplate = Just "$body$\n" }) . toPandoc) + "minimal heading levels" $ + header 2 (text "Header 1") <> + header 3 (text "Header 2") <> + header 2 (text "Header 1") <> + header 4 (text "Header 2") <> + header 5 (text "Header 3") <> + header 3 (text "Header 2") =?> + unlines + [ "Header 1" + , "========" + , "" + , "Header 2" + , "--------" + , "" + , "Header 1" + , "========" + , "" + , "Header 2" + , "--------" + , "" + , "Header 3" + , "~~~~~~~~" + , "" + , "Header 2" + , "--------"] + ] + ] diff --git a/test/Tests/Writers/TEI.hs.orig b/test/Tests/Writers/TEI.hs.orig new file mode 100644 index 000000000..fa372909f --- /dev/null +++ b/test/Tests/Writers/TEI.hs.orig @@ -0,0 +1,43 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.TEI (tests) where + +import Test.Tasty +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder + +{- + "my test" =: X =?> Y + +is shorthand for + + test html "my test" $ X =?> Y + +which is in turn shorthand for + + test html "my test" (X,Y) +-} + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> TestTree +(=:) = test (purely (writeTEI def) . toPandoc) + +tests :: [TestTree] +tests = [ testGroup "block elements" + ["para" =: para "Lorem ipsum cetera." + =?> "

Lorem ipsum cetera.

" + ] + , testGroup "inlines" + [ + "Emphasis" =: emph "emphasized" + =?> "

emphasized

" + ,"SingleQuoted" =: singleQuoted (text "quoted material") + =?> "

quoted material

" + ,"DoubleQuoted" =: doubleQuoted (text "quoted material") + =?> "

quoted material

" + ,"NestedQuoted" =: doubleQuoted (singleQuoted (text "quoted material")) + =?> "

quoted material

" + ] + ] diff --git a/test/command/3510-src.hs.orig b/test/command/3510-src.hs.orig new file mode 100644 index 000000000..ad5744b80 --- /dev/null +++ b/test/command/3510-src.hs.orig @@ -0,0 +1 @@ +putStrLn outString diff --git a/test/command/4550.md b/test/command/4550.md new file mode 100644 index 000000000..bf3afce5b --- /dev/null +++ b/test/command/4550.md @@ -0,0 +1,7 @@ +``` +% pandoc -f markdown-smart -t ms +A ‘simple’ example +^D +.LP +A ‘simple’ example +``` diff --git a/test/pandoc-test14632-86 b/test/pandoc-test14632-86 new file mode 100644 index 000000000..507e9f672 --- /dev/null +++ b/test/pandoc-test14632-86 @@ -0,0 +1,1448 @@ + + +
+ + + + + + + + + + +Pandoc Test Suite + + + + +John MacFarlane + + + + +Anonymous + + + + +July 17, 2006 + + + + +

+ This is a set of tests for pandoc. Most of them are adapted from John + Gruber’s markdown test suite. +

+ + Headers + + Level 2 with an + <ext-link ext-link-type="uri" xlink:href="/url">embedded + link</ext-link> + + Level 3 with <italic>emphasis</italic> + + Level 4 + + Level 5 + + + + + + + Level 1 + + Level 2 with <italic>emphasis</italic> + + Level 3 +

+ with no blank line +

+
+
+ + Level 2 +

+ with no blank line +

+
+
+ + Paragraphs +

+ Here’s a regular paragraph. +

+

+ In Markdown 1.0.0 and earlier. Version 8. This line turns into a list + item. Because a hard-wrapped line in the middle of a paragraph looked like + a list item. +

+

+ Here’s one with a bullet. * criminey. +

+

+ There should be a hard line breakhere. +

+
+ + Block Quotes +

+ E-mail style: +

+ +

+ This is a block quote. It is pretty short. +

+
+ +

+ Code in a block quote: +

+ sub status { + print "working"; +} +

+ A list: +

+ + +

+ item one +

+
+ +

+ item two +

+
+
+

+ Nested block quotes: +

+ +

+ nested +

+
+ +

+ nested +

+
+
+

+ This should not be a block quote: 2 > 1. +

+

+ And a following paragraph. +

+
+ + Code Blocks +

+ Code: +

+ ---- (should be four hyphens) + +sub status { + print "working"; +} + +this code block is indented by one tab +

+ And: +

+ this code block is indented by two tabs + +These should not be escaped: \$ \\ \> \[ \{ +
+ + Lists + + Unordered +

+ Asterisks tight: +

+ + +

+ asterisk 1 +

+
+ +

+ asterisk 2 +

+
+ +

+ asterisk 3 +

+
+
+

+ Asterisks loose: +

+ + +

+ asterisk 1 +

+
+ +

+ asterisk 2 +

+
+ +

+ asterisk 3 +

+
+
+

+ Pluses tight: +

+ + +

+ Plus 1 +

+
+ +

+ Plus 2 +

+
+ +

+ Plus 3 +

+
+
+

+ Pluses loose: +

+ + +

+ Plus 1 +

+
+ +

+ Plus 2 +

+
+ +

+ Plus 3 +

+
+
+

+ Minuses tight: +

+ + +

+ Minus 1 +

+
+ +

+ Minus 2 +

+
+ +

+ Minus 3 +

+
+
+

+ Minuses loose: +

+ + +

+ Minus 1 +

+
+ +

+ Minus 2 +

+
+ +

+ Minus 3 +

+
+
+
+ + Ordered +

+ Tight: +

+ + +

+ First +

+
+ +

+ Second +

+
+ +

+ Third +

+
+
+

+ and: +

+ + +

+ One +

+
+ +

+ Two +

+
+ +

+ Three +

+
+
+

+ Loose using tabs: +

+ + +

+ First +

+
+ +

+ Second +

+
+ +

+ Third +

+
+
+

+ and using spaces: +

+ + +

+ One +

+
+ +

+ Two +

+
+ +

+ Three +

+
+
+

+ Multiple paragraphs: +

+ + +

+ Item 1, graf one. +

+

+ Item 1. graf two. The quick brown fox jumped over the lazy dog’s + back. +

+
+ +

+ Item 2. +

+
+ +

+ Item 3. +

+
+
+
+ + Nested + + +

+ Tab +

+ + +

+ Tab +

+ + +

+ Tab +

+
+
+
+
+
+
+

+ Here’s another: +

+ + +

+ First +

+
+ +

+ Second: +

+ + +

+ Fee +

+
+ +

+ Fie +

+
+ +

+ Foe +

+
+
+
+ +

+ Third +

+
+
+

+ Same thing but with paragraphs: +

+ + +

+ First +

+
+ +

+ Second: +

+ + +

+ Fee +

+
+ +

+ Fie +

+
+ +

+ Foe +

+
+
+
+ +

+ Third +

+
+
+
+ + Tabs and spaces + + +

+ this is a list item indented with tabs +

+
+ +

+ this is a list item indented with spaces +

+ + +

+ this is an example list item indented with tabs +

+
+ +

+ this is an example list item indented with spaces +

+
+
+
+
+
+ + Fancy list markers + + + +

+ begins with 2 +

+
+ + +

+ and now 3 +

+

+ with a continuation +

+ + + +

+ sublist with roman numerals, starting with 4 +

+
+ + +

+ more items +

+ + + +

+ a subsublist +

+
+ + +

+ a subsublist +

+
+
+
+
+
+
+

+ Nesting: +

+ + +

+ Upper Alpha +

+ + +

+ Upper Roman. +

+ + + +

+ Decimal start with 6 +

+ + + +

+ Lower alpha with paren +

+
+
+
+
+
+
+
+
+

+ Autonumbering: +

+ + +

+ Autonumber. +

+
+ +

+ More. +

+ + +

+ Nested. +

+
+
+
+
+

+ Should not be a list item: +

+

+ M.A. 2007 +

+

+ B. Williams +

+
+
+ + Definition Lists +

+ Tight using spaces: +

+ + + + apple + + +

+ red fruit +

+
+
+ + + orange + + +

+ orange fruit +

+
+
+ + + banana + + +

+ yellow fruit +

+
+
+
+

+ Tight using tabs: +

+ + + + apple + + +

+ red fruit +

+
+
+ + + orange + + +

+ orange fruit +

+
+
+ + + banana + + +

+ yellow fruit +

+
+
+
+

+ Loose: +

+ + + + apple + + +

+ red fruit +

+
+
+ + + orange + + +

+ orange fruit +

+
+
+ + + banana + + +

+ yellow fruit +

+
+
+
+

+ Multiple blocks with italics: +

+ + + + apple + + +

+ red fruit +

+

+ contains seeds, crisp, pleasant to taste +

+
+
+ + + orange + + +

+ orange fruit +

+ { orange code block } + +

+ orange block quote +

+
+
+
+
+

+ Multiple definitions, tight: +

+ + + + apple + + +

+ red fruit +

+

+ computer +

+
+
+ + + orange + + +

+ orange fruit +

+

+ bank +

+
+
+
+

+ Multiple definitions, loose: +

+ + + + apple + + +

+ red fruit +

+

+ computer +

+
+
+ + + orange + + +

+ orange fruit +

+

+ bank +

+
+
+
+

+ Blank line after term, indented marker, alternate markers: +

+ + + + apple + + +

+ red fruit +

+

+ computer +

+
+
+ + + orange + + +

+ orange fruit +

+ + +

+ sublist +

+
+ +

+ sublist +

+
+
+
+
+
+
+ + HTML Blocks +

+ Simple block on one line: +

+ +

+ foo +

+
+

+ And nested without indentation: +

+ + + +

+ foo +

+
+
+ +

+ bar +

+
+
+

+ Interpreted markdown in a table: +

+

+ This is emphasized +

+

+ And this is strong +

+

+ Here’s a simple block: +

+ +

+ foo +

+
+

+ This should be a code block, though: +

+ <div> + foo +</div> +

+ As should this: +

+ <div>foo</div> +

+ Now, nested: +

+ + + +

+ foo +

+
+
+
+

+ This should just be an HTML comment: +

+

+ Multiline: +

+

+ Code block: +

+ <!-- Comment --> +

+ Just plain comment, with trailing spaces on the line: +

+

+ Code: +

+ <hr /> +

+ Hr’s: +

+
+ + Inline Markup +

+ This is emphasized, and so is this. +

+

+ This is strong, and so is + this. +

+

+ An emphasized + link. +

+

+ This is strong and em. +

+

+ So is this word. +

+

+ This is strong and em. +

+

+ So is this word. +

+

+ This is code: >, $, + \, \$, + <html>. +

+

+ This is strikeout. +

+

+ Superscripts: abcd ahello + ahello there. +

+

+ Subscripts: H2O, H23O, Hmany of themO. +

+

+ These should not be superscripts or subscripts, because of the unescaped + spaces: a^b c^d, a~b c~d. +

+
+ + Smart quotes, ellipses, dashes +

+ “Hello,” said the spider. “‘Shelob’ is my name.” +

+

+ ‘A’, ‘B’, and ‘C’ are letters. +

+

+ ‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’ +

+

+ ‘He said, “I want to go.”’ Were you alive in the 70’s? +

+

+ Here is some quoted ‘code’ and a + “quoted + link”. +

+

+ Some dashes: one—two — three—four — five. +

+

+ Dashes between numbers: 5–7, 255–66, 1987–1999. +

+

+ Ellipses…and…and…. +

+
+ + LaTeX + + +

+

+
+ +

+ + + 2+2=4 +

+
+ +

+ + + xy +

+
+ +

+ + + αω +

+
+ +

+ + + 223 +

+
+ +

+ + + p-Tree +

+
+ +

+ Here’s some display math: + + ddxf(x)=limh0f(x+h)f(x)h +

+
+ +

+ Here’s one that has a line break in it: + + α+ω×x2. +

+
+
+

+ These shouldn’t be math: +

+ + +

+ To get the famous equation, write $e = mc^2$. +

+
+ +

+ $22,000 is a lot of money. So is $34,000. (It worked + if “lot” is emphasized.) +

+
+ +

+ Shoes ($20) and socks ($5). +

+
+ +

+ Escaped $: $73 this should be + emphasized 23$. +

+
+
+

+ Here’s a LaTeX table: +

+
+ + Special Characters +

+ Here is some unicode: +

+ + +

+ I hat: Î +

+
+ +

+ o umlaut: ö +

+
+ +

+ section: § +

+
+ +

+ set membership: ∈ +

+
+ +

+ copyright: © +

+
+
+

+ AT&T has an ampersand in their name. +

+

+ AT&T is another way to write it. +

+

+ This & that. +

+

+ 4 < 5. +

+

+ 6 > 5. +

+

+ Backslash: \ +

+

+ Backtick: ` +

+

+ Asterisk: * +

+

+ Underscore: _ +

+

+ Left brace: { +

+

+ Right brace: } +

+

+ Left bracket: [ +

+

+ Right bracket: ] +

+

+ Left paren: ( +

+

+ Right paren: ) +

+

+ Greater-than: > +

+

+ Hash: # +

+

+ Period: . +

+

+ Bang: ! +

+

+ Plus: + +

+

+ Minus: - +

+
+ + Links + + Explicit +

+ Just a URL. +

+

+ URL + and title. +

+

+ URL + and title. +

+

+ URL + and title. +

+

+ URL + and title +

+

+ URL + and title +

+

+ with_underscore +

+

+ Email + link +

+

+ Empty. +

+
+ + Reference +

+ Foo bar. +

+

+ With embedded + [brackets]. +

+

+ b by itself + should be a link. +

+

+ Indented + once. +

+

+ Indented + twice. +

+

+ Indented + thrice. +

+

+ This should [not][] be a link. +

+ [not]: /url +

+ Foo + bar. +

+

+ Foo + biz. +

+
+ + With ampersands +

+ Here’s a + link + with an ampersand in the URL. +

+

+ Here’s a link with an amersand in the link text: + AT&T. +

+

+ Here’s an + inline + link. +

+

+ Here’s an + inline + link in pointy braces. +

+
+ + Autolinks +

+ With an ampersand: + http://example.com/?foo=1&bar=2 +

+ + +

+ In a list? +

+
+ +

+ http://example.com/ +

+
+ +

+ It should. +

+
+
+

+ An e-mail address: nobody@nowhere.net +

+ +

+ Blockquoted: + http://example.com/ +

+
+

+ Auto-links should not occur here: + <http://example.com/> +

+ or here: <http://example.com/> +
+
+ + Images +

+ From “Voyage dans la Lune” by Georges Melies (1902): +

+ + lalune + + +

+ Here is a movie + + icon. +

+
+ + Footnotes +

+ Here is a footnote reference, +

+ Here is the footnote. It can go anywhere after the footnote reference. + It need not be placed at the end of the document. +

+ and another. +

+ Here’s the long note. This one contains multiple blocks. +

+

+ Subsequent blocks are indented to show that they belong to the + footnote (as with list items). +

+ { <code> } +

+ If you want, you can indent every line, but you can also be lazy and + just indent the first line of each block. +

+
This should not be a footnote reference, because it + contains a space.[^my note] Here is an inline note. +

+ This is easier to type. Inline notes may contain + links + and ] verbatim characters, as well as + [bracketed text]. +

+
+

+ +

+ Notes can go in quotes. +

+ In quote. +

+ +

+
+ + +

+ And in list items. +

+ In list. +

+ +

+
+
+

+ This paragraph should not be part of the note, as it is not indented. +

+
+ + + +
diff --git a/test/pandoc-test14632-89 b/test/pandoc-test14632-89 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test14632-90 b/test/pandoc-test14632-90 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test14632-91 b/test/pandoc-test14632-91 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test14632-94 b/test/pandoc-test14632-94 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test14632-95 b/test/pandoc-test14632-95 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test14632-96 b/test/pandoc-test14632-96 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test14632-97 b/test/pandoc-test14632-97 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test77993-78 b/test/pandoc-test77993-78 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test77993-79 b/test/pandoc-test77993-79 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test77993-82 b/test/pandoc-test77993-82 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test77993-83 b/test/pandoc-test77993-83 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test77993-86 b/test/pandoc-test77993-86 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test77993-87 b/test/pandoc-test77993-87 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test77993-90 b/test/pandoc-test77993-90 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test77993-91 b/test/pandoc-test77993-91 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test88473-110 b/test/pandoc-test88473-110 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test88473-111 b/test/pandoc-test88473-111 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test88473-112 b/test/pandoc-test88473-112 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test88473-113 b/test/pandoc-test88473-113 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test88473-116 b/test/pandoc-test88473-116 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test88473-117 b/test/pandoc-test88473-117 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test88473-118 b/test/pandoc-test88473-118 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test88473-119 b/test/pandoc-test88473-119 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test94017-86 b/test/pandoc-test94017-86 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test94017-87 b/test/pandoc-test94017-87 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test94017-90 b/test/pandoc-test94017-90 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test94017-91 b/test/pandoc-test94017-91 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test94017-92 b/test/pandoc-test94017-92 new file mode 100644 index 000000000..e69de29bb diff --git a/test/pandoc-test94017-93 b/test/pandoc-test94017-93 new file mode 100644 index 000000000..e69de29bb diff --git a/test/tables.ms b/test/tables.ms index 21b3bd4e2..1ef6b52f4 100644 --- a/test/tables.ms +++ b/test/tables.ms @@ -135,7 +135,7 @@ T} .LP Multiline table with caption: .PP -Here's the caption. It may span multiple lines. +Here’s the caption. It may span multiple lines. .TS delim(@@) tab( ); cw(10.5n) lw(9.6n) rw(11.4n) lw(23.6n). @@ -165,7 +165,7 @@ row T} T{ 5.0 T} T{ -Here's another one. +Here’s another one. Note the blank line between rows. T} .TE @@ -201,7 +201,7 @@ row T} T{ 5.0 T} T{ -Here's another one. +Here’s another one. Note the blank line between rows. T} .TE @@ -261,7 +261,7 @@ row T} T{ 5.0 T} T{ -Here's another one. +Here’s another one. Note the blank line between rows. T} .TE diff --git a/test/test-pandoc.hs.orig b/test/test-pandoc.hs.orig new file mode 100644 index 000000000..4cf1a952d --- /dev/null +++ b/test/test-pandoc.hs.orig @@ -0,0 +1,83 @@ +{-# OPTIONS_GHC -Wall #-} + +module Main where + +import GHC.IO.Encoding +import Test.Tasty +import qualified Tests.Command +import qualified Tests.Lua +import qualified Tests.Old +import qualified Tests.Readers.Creole +import qualified Tests.Readers.Docx +import qualified Tests.Readers.EPUB +import qualified Tests.Readers.HTML +import qualified Tests.Readers.JATS +import qualified Tests.Readers.LaTeX +import qualified Tests.Readers.Markdown +import qualified Tests.Readers.Muse +import qualified Tests.Readers.Odt +import qualified Tests.Readers.Org +import qualified Tests.Readers.RST +import qualified Tests.Readers.Txt2Tags +import qualified Tests.Shared +import qualified Tests.Writers.AsciiDoc +import qualified Tests.Writers.ConTeXt +import qualified Tests.Writers.Docbook +import qualified Tests.Writers.Docx +import qualified Tests.Writers.FB2 +import qualified Tests.Writers.HTML +import qualified Tests.Writers.JATS +import qualified Tests.Writers.LaTeX +import qualified Tests.Writers.Markdown +import qualified Tests.Writers.Muse +import qualified Tests.Writers.Native +import qualified Tests.Writers.Org +import qualified Tests.Writers.Plain +import qualified Tests.Writers.Powerpoint +import qualified Tests.Writers.RST +import qualified Tests.Writers.TEI +import Text.Pandoc.Shared (inDirectory) + +tests :: TestTree +tests = testGroup "pandoc tests" [ Tests.Command.tests + , testGroup "Old" Tests.Old.tests + , testGroup "Shared" Tests.Shared.tests + , testGroup "Writers" + [ testGroup "Native" Tests.Writers.Native.tests + , testGroup "ConTeXt" Tests.Writers.ConTeXt.tests + , testGroup "LaTeX" Tests.Writers.LaTeX.tests + , testGroup "HTML" Tests.Writers.HTML.tests + , testGroup "JATS" Tests.Writers.JATS.tests + , testGroup "Docbook" Tests.Writers.Docbook.tests + , testGroup "Markdown" Tests.Writers.Markdown.tests + , testGroup "Org" Tests.Writers.Org.tests + , testGroup "Plain" Tests.Writers.Plain.tests + , testGroup "AsciiDoc" Tests.Writers.AsciiDoc.tests + , testGroup "Docx" Tests.Writers.Docx.tests + , testGroup "RST" Tests.Writers.RST.tests + , testGroup "TEI" Tests.Writers.TEI.tests + , testGroup "Muse" Tests.Writers.Muse.tests + , testGroup "FB2" Tests.Writers.FB2.tests + , testGroup "PowerPoint" Tests.Writers.Powerpoint.tests + ] + , testGroup "Readers" + [ testGroup "LaTeX" Tests.Readers.LaTeX.tests + , testGroup "Markdown" Tests.Readers.Markdown.tests + , testGroup "HTML" Tests.Readers.HTML.tests + , testGroup "JATS" Tests.Readers.JATS.tests + , testGroup "Org" Tests.Readers.Org.tests + , testGroup "RST" Tests.Readers.RST.tests + , testGroup "Docx" Tests.Readers.Docx.tests + , testGroup "Odt" Tests.Readers.Odt.tests + , testGroup "Txt2Tags" Tests.Readers.Txt2Tags.tests + , testGroup "EPUB" Tests.Readers.EPUB.tests + , testGroup "Muse" Tests.Readers.Muse.tests + , testGroup "Creole" Tests.Readers.Creole.tests + ] + , testGroup "Lua filters" Tests.Lua.tests + ] + +main :: IO () +main = do + setLocaleEncoding utf8 + inDirectory "test" $ defaultMain tests diff --git a/test/writer.ms b/test/writer.ms index a9ca07259..a95b5fe33 100644 --- a/test/writer.ms +++ b/test/writer.ms @@ -72,7 +72,7 @@ Anonymous .1C .LP This is a set of tests for pandoc. -Most of them are adapted from John Gruber's markdown test suite. +Most of them are adapted from John Gruber’s markdown test suite. .HLINE .SH 1 Headers @@ -123,7 +123,7 @@ Paragraphs .pdfhref O 1 "Paragraphs" .pdfhref M "paragraphs" .LP -Here's a regular paragraph. +Here’s a regular paragraph. .PP In Markdown 1.0.0 and earlier. Version 8. @@ -131,7 +131,7 @@ This line turns into a list item. Because a hard-wrapped line in the middle of a paragraph looked like a list item. .PP -Here's one with a bullet. +Here’s one with a bullet. * criminey. .PP There should be a hard line break @@ -311,7 +311,7 @@ Item 1, graf one. .PP Item 1. graf two. -The quick brown fox jumped over the lazy dog's back. +The quick brown fox jumped over the lazy dog’s back. .RE .IP " 2." 4 Item 2. @@ -332,7 +332,7 @@ Tab .RE .RE .LP -Here's another: +Here’s another: .IP " 1." 4 First .IP " 2." 4 @@ -567,7 +567,7 @@ Interpreted markdown in a table: This is \f[I]emphasized\f[] And this is \f[B]strong\f[] .PP -Here's a simple block: +Here’s a simple block: .LP foo .LP @@ -614,7 +614,7 @@ Code: \f[] .fi .LP -Hr's: +Hr’s: .HLINE .SH 1 Inline Markup @@ -663,7 +663,7 @@ Smart quotes, ellipses, dashes `Oak,' `elm,' and `beech' are names of trees. So is `pine.' .PP -`He said, \[lq]I want to go.\[rq]' Were you alive in the 70's? +`He said, \[lq]I want to go.\[rq]' Were you alive in the 70’s? .PP Here is some quoted `\f[C]code\f[]' and a \[lq]\c .pdfhref W -D "http://example.com/?foo=1&bar=2" -A "\c" \ @@ -692,14 +692,14 @@ LaTeX .IP \[bu] 3 @p@-Tree .IP \[bu] 3 -Here's some display math: +Here’s some display math: .EQ d over {d x} f ( x ) = lim sub {h -> 0} {f ( x + h ) \[u2212] f ( x )} over h .EN .IP \[bu] 3 -Here's one that has a line break in it: @alpha + omega times x sup 2@. +Here’s one that has a line break in it: @alpha + omega times x sup 2@. .LP -These shouldn't be math: +These shouldn’t be math: .IP \[bu] 3 To get the famous equation, write \f[C]$e\ =\ mc\[ha]2$\f[]. .IP \[bu] 3 @@ -711,7 +711,7 @@ Shoes ($20) and socks ($5). .IP \[bu] 3 Escaped \f[C]$\f[]: $73 \f[I]this should be emphasized\f[] 23$. .LP -Here's a LaTeX table: +Here’s a LaTeX table: .HLINE .SH 1 Special Characters @@ -882,22 +882,22 @@ With ampersands .pdfhref O 2 "With ampersands" .pdfhref M "with-ampersands" .LP -Here's a \c +Here’s a \c .pdfhref W -D "http://example.com/?foo=1&bar=2" -A "\c" \ -- "link with an ampersand in the URL" \&. .PP -Here's a link with an amersand in the link text: \c +Here’s a link with an amersand in the link text: \c .pdfhref W -D "http://att.com/" -A "\c" \ -- "AT&T" \&. .PP -Here's an \c +Here’s an \c .pdfhref W -D "/script?foo=1&bar=2" -A "\c" \ -- "inline link" \&. .PP -Here's an \c +Here’s an \c .pdfhref W -D "/script?foo=1&bar=2" -A "\c" \ -- "inline link in pointy braces" \&. @@ -964,7 +964,7 @@ It need not be placed at the end of the document. .FE and another.\** .FS -Here's the long note. +Here’s the long note. This one contains multiple blocks. .PP Subsequent blocks are indented to show that they belong to the footnote (as -- cgit v1.2.3 From 16439c879e21749e96d8f7a0ed58c87b0c235cb0 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 14 Apr 2018 10:59:01 -0700 Subject: Ms writer link improvements. + Create pdf anchor for a Div with an identifier. + Escape `/` character in anchor ids. + Improve escaping for anchor ids: we now use _uNNN_ instead of uNNN to avoid ambiguity. This is intended to help with #4515; however, in my tests, the link to the reference does not seem to work. I'm not sure why. --- src/Text/Pandoc/Writers/Ms.hs | 18 +++++++++++++----- 1 file changed, 13 insertions(+), 5 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Writers/Ms.hs b/src/Text/Pandoc/Writers/Ms.hs index 75c904245..4731d4a9f 100644 --- a/src/Text/Pandoc/Writers/Ms.hs +++ b/src/Text/Pandoc/Writers/Ms.hs @@ -217,11 +217,16 @@ blockToMs :: PandocMonad m -> Block -- ^ Block element -> MS m Doc blockToMs _ Null = return empty -blockToMs opts (Div _ bs) = do +blockToMs opts (Div (ident,_,_) bs) = do + let anchor = if null ident + then empty + else nowrap $ + text ".pdfhref M " + <> doubleQuotes (text (toAscii ident)) setFirstPara res <- blockListToMs opts bs setFirstPara - return res + return $ anchor $$ res blockToMs opts (Plain inlines) = liftM vcat $ mapM (inlineListToMs' opts) $ splitSentences inlines blockToMs opts (Para [Image attr alt (src,_tit)]) @@ -640,7 +645,10 @@ highlightCode opts attr str = modify (\st -> st{ stHighlighting = True }) return h +-- This is used for PDF anchors. toAscii :: String -> String -toAscii = concatMap (\c -> case toAsciiChar c of - Nothing -> 'u':show (ord c) - Just c' -> [c']) +toAscii = concatMap + (\c -> case toAsciiChar c of + Nothing -> '_':'u':show (ord c) ++ "_" + Just '/' -> '_':'u':show (ord c) ++ "_" -- see #4515 + Just c' -> [c']) -- cgit v1.2.3 From 34d8ffbcfc33b86766ff7229be4d8a0d1fbffb50 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 14 Apr 2018 17:44:44 -0700 Subject: Added a needed import in Text.Pandoc.App. --- src/Text/Pandoc/App.hs | 1 + 1 file changed, 1 insertion(+) (limited to 'src') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index b3c51211a..b124bdda0 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -69,6 +69,7 @@ import Network.URI (URI (..), parseURI) #ifdef EMBED_DATA_FILES import Text.Pandoc.Data (dataFiles) #else +import System.Directory (getDirectoryContents) import Paths_pandoc (getDataDir) #endif import Data.Aeson.Encode.Pretty (encodePretty', Config(..), keyOrder, -- cgit v1.2.3 From 6be013914513d2dd8ef7f141b1e3fd59cee7d3f7 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Sun, 15 Apr 2018 12:17:15 +0300 Subject: Muse reader: require that comment semicolons are in the first column Fixes #4551 --- src/Text/Pandoc/Readers/Muse.hs | 1 + test/Tests/Readers/Muse.hs | 1 + 2 files changed, 2 insertions(+) (limited to 'src') diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs index 9763652bc..0da8bbdcc 100644 --- a/src/Text/Pandoc/Readers/Muse.hs +++ b/src/Text/Pandoc/Readers/Muse.hs @@ -348,6 +348,7 @@ blockElements = do -- | Parse a line comment, starting with @;@ in the first column. comment :: PandocMonad m => MuseParser m (F Blocks) comment = try $ do + getPosition >>= \pos -> guard (sourceColumn pos == 1) char ';' optional (spaceChar >> many (noneOf "\n")) eol diff --git a/test/Tests/Readers/Muse.hs b/test/Tests/Readers/Muse.hs index 11eebbdc0..188036a09 100644 --- a/test/Tests/Readers/Muse.hs +++ b/test/Tests/Readers/Muse.hs @@ -521,6 +521,7 @@ tests = , "Text after empty comment" =: ";\nfoo" =?> para "foo" -- Make sure we don't consume newline while looking for whitespace , "Not a comment (does not start with a semicolon)" =: " ; Not a comment" =?> para (text "; Not a comment") , "Not a comment (has no space after semicolon)" =: ";Not a comment" =?> para (text ";Not a comment") + , "Not a comment (semicolon not in the first column)" =: " - ; foo" =?> bulletList [para "; foo"] ] , testGroup "Headers" [ "Part" =: -- cgit v1.2.3 From 9cc2bf0295a66182223c9ec421a4755d1acebeb1 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Sun, 15 Apr 2018 14:50:46 +0300 Subject: Muse reader: allow URL to be empty Muse writer can write links with empty URLs, so Muse reader should read them. --- src/Text/Pandoc/Readers/Muse.hs | 2 +- test/Tests/Readers/Muse.hs | 1 + 2 files changed, 2 insertions(+), 1 deletion(-) (limited to 'src') diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs index 0da8bbdcc..0dba0c4cb 100644 --- a/src/Text/Pandoc/Readers/Muse.hs +++ b/src/Text/Pandoc/Readers/Muse.hs @@ -972,7 +972,7 @@ linkContent = char '[' >> trimInlinesF . mconcat <$> manyTill inline (string "]" linkText :: PandocMonad m => MuseParser m (String, Maybe (F Inlines)) linkText = do string "[[" - url <- many1Till anyChar $ char ']' + url <- manyTill anyChar $ char ']' content <- optionMaybe linkContent char ']' return (url, content) diff --git a/test/Tests/Readers/Muse.hs b/test/Tests/Readers/Muse.hs index 188036a09..11ec9464f 100644 --- a/test/Tests/Readers/Muse.hs +++ b/test/Tests/Readers/Muse.hs @@ -209,6 +209,7 @@ tests = -- This test also makes sure '=' without whitespace is not treated as code markup , "No implicit links" =: "http://example.org/index.php?action=view&id=1" =?> para "http://example.org/index.php?action=view&id=1" + , "Link with empty URL" =: "[[][empty URL]]" =?> para (link "" "" (text "empty URL")) ] , testGroup "Literal" -- cgit v1.2.3 From 17767bd29d54883364d4d9bdee417973ac0a10ac Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Sun, 15 Apr 2018 16:07:43 +0300 Subject: Muse writer: escape strings starting with space --- src/Text/Pandoc/Writers/Muse.hs | 6 +++++- test/Tests/Writers/Muse.hs | 9 +++++++++ 2 files changed, 14 insertions(+), 1 deletion(-) (limited to 'src') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 127a4f149..4e7ce377a 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -400,6 +400,10 @@ isHorizontalRule s = ((length xs) >= 4) && null ys where (xs, ys) = span (== '-') s +startsWithSpace :: String -> Bool +startsWithSpace (x:_) = isSpace x +startsWithSpace [] = False + fixOrEscape :: Bool -> Inline -> Bool fixOrEscape sp (Str "-") = sp fixOrEscape sp (Str ";") = not sp @@ -407,7 +411,7 @@ fixOrEscape _ (Str ">") = True fixOrEscape sp (Str s) = (sp && (startsWithMarker isDigit s || startsWithMarker isAsciiLower s || startsWithMarker isAsciiUpper s)) - || isHorizontalRule s + || isHorizontalRule s || startsWithSpace s fixOrEscape _ Space = True fixOrEscape _ SoftBreak = True fixOrEscape _ _ = False diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index 41c846b1b..44fdd5b7e 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -112,6 +112,15 @@ tests = [ testGroup "block elements" , " :: second description" , " :: third description" ] + , "definition list terms starting with space" =: + definitionList [ (text "first definition", [plain $ text "first description"]) + , (space <> str "foo", [plain $ text "second description"]) + , (str " > bar", [plain $ text "third description"]) + ] + =?> unlines [ " first definition :: first description" + , " foo :: second description" + , " > bar :: third description" + ] ] -- Test that lists of the same type and style are separated with two blanklines , testGroup "sequential lists" -- cgit v1.2.3 From 01f5ed14e67d0f4f3bf23b9506fe91b226cfe769 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Sun, 15 Apr 2018 17:40:36 +0300 Subject: Muse reader: don't allow footnote references inside links --- src/Text/Pandoc/Readers/Muse.hs | 2 ++ test/Tests/Readers/Muse.hs | 3 +++ 2 files changed, 5 insertions(+) (limited to 'src') diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs index 0dba0c4cb..c417588b8 100644 --- a/src/Text/Pandoc/Readers/Muse.hs +++ b/src/Text/Pandoc/Readers/Muse.hs @@ -822,6 +822,8 @@ anchor = try $ do -- | Parse a footnote reference. footnote :: PandocMonad m => MuseParser m (F Inlines) footnote = try $ do + inLink <- museInLink <$> getState + guard $ not inLink ref <- noteMarker return $ do notes <- asksF museNotes diff --git a/test/Tests/Readers/Muse.hs b/test/Tests/Readers/Muse.hs index 11ec9464f..5c7460afe 100644 --- a/test/Tests/Readers/Muse.hs +++ b/test/Tests/Readers/Muse.hs @@ -210,6 +210,9 @@ tests = , "No implicit links" =: "http://example.org/index.php?action=view&id=1" =?> para "http://example.org/index.php?action=view&id=1" , "Link with empty URL" =: "[[][empty URL]]" =?> para (link "" "" (text "empty URL")) + , "No footnotes inside links" =: + "[[https://amusewiki.org/][foo[1]]" =?> + para (link "https://amusewiki.org/" "" (text "foo[1")) ] , testGroup "Literal" -- cgit v1.2.3 From 8ca012f139d09d77a878e049cf9972efc026674e Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 15 Apr 2018 22:44:16 -0700 Subject: Ms writer: font improvements. * Use `\f[R]` rather than `\f[]` to reset. The latter returns to the previous font, which gives unintended results in some cases. * Use `\f[BI]` and `\f[CB]` in headers, instead of `\f[I]` and `\f[C]`, since the header font is automatically bold. * Use `\f[CB]` rather than `\f[BC]` for monospace bold. Closes #4552. --- src/Text/Pandoc/Writers/Ms.hs | 17 ++++++++++++--- test/writer.ms | 50 +++++++++++++++++++++---------------------- 2 files changed, 39 insertions(+), 28 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Writers/Ms.hs b/src/Text/Pandoc/Writers/Ms.hs index 4731d4a9f..16a66c85b 100644 --- a/src/Text/Pandoc/Writers/Ms.hs +++ b/src/Text/Pandoc/Writers/Ms.hs @@ -40,7 +40,7 @@ module Text.Pandoc.Writers.Ms ( writeMs ) where import Prelude import Control.Monad.State.Strict import Data.Char (isLower, isUpper, toUpper, ord) -import Data.List (intercalate, intersperse, sort) +import Data.List (intercalate, intersperse) import qualified Data.Map as Map import Data.Maybe (catMaybes, fromMaybe) import Data.Text (Text) @@ -68,6 +68,7 @@ data WriterState = WriterState { stHasInlineMath :: Bool , stNotes :: [Note] , stSmallCaps :: Bool , stHighlighting :: Bool + , stInHeader :: Bool , stFontFeatures :: Map.Map Char Bool } @@ -77,6 +78,7 @@ defaultWriterState = WriterState{ stHasInlineMath = False , stNotes = [] , stSmallCaps = False , stHighlighting = False + , stInHeader = False , stFontFeatures = Map.fromList [ ('I',False) , ('B',False) @@ -264,7 +266,9 @@ blockToMs _ HorizontalRule = do return $ text ".HLINE" blockToMs opts (Header level (ident,classes,_) inlines) = do setFirstPara + modify $ \st -> st{ stInHeader = True } contents <- inlineListToMs' opts $ map breakToSpace inlines + modify $ \st -> st{ stInHeader = False } let (heading, secnum) = if writerNumberSections opts && "unnumbered" `notElem` classes then (".NH", "\\*[SN]") @@ -559,8 +563,15 @@ handleNote opts bs = do fontChange :: PandocMonad m => MS m Doc fontChange = do features <- gets stFontFeatures - let filling = sort [c | (c,True) <- Map.toList features] - return $ text $ "\\f[" ++ filling ++ "]" + inHeader <- gets stInHeader + let filling = ['C' | fromMaybe False $ Map.lookup 'C' features] ++ + ['B' | inHeader || + fromMaybe False (Map.lookup 'B' features)] ++ + ['I' | fromMaybe False $ Map.lookup 'I' features] + return $ + if null filling + then text "\\f[R]" + else text $ "\\f[" ++ filling ++ "]" withFontFeature :: PandocMonad m => Char -> MS m Doc -> MS m Doc withFontFeature c action = do diff --git a/test/writer.ms b/test/writer.ms index a95b5fe33..33dec71d3 100644 --- a/test/writer.ms +++ b/test/writer.ms @@ -86,7 +86,7 @@ Level 2 with an \c .pdfhref O 2 "Level 2 with an embedded link" .pdfhref M "level-2-with-an-embedded-link" .SH 3 -Level 3 with \f[I]emphasis\f[] +Level 3 with \f[BI]emphasis\f[B] .pdfhref O 3 "Level 3 with emphasis" .pdfhref M "level-3-with-emphasis" .SH 4 @@ -102,7 +102,7 @@ Level 1 .pdfhref O 1 "Level 1" .pdfhref M "level-1" .SH 2 -Level 2 with \f[I]emphasis\f[] +Level 2 with \f[BI]emphasis\f[B] .pdfhref O 2 "Level 2 with emphasis" .pdfhref M "level-2-with-emphasis" .SH 3 @@ -481,13 +481,13 @@ yellow fruit .RE .LP Multiple blocks with italics: -.IP "\f[I]apple\f[]" +.IP "\f[I]apple\f[R]" red fruit .RS .PP contains seeds, crisp, pleasant to taste .RE -.IP "\f[I]orange\f[]" +.IP "\f[I]orange\f[R]" orange fruit .RS .IP @@ -564,8 +564,8 @@ foo bar .LP Interpreted markdown in a table: -This is \f[I]emphasized\f[] -And this is \f[B]strong\f[] +This is \f[I]emphasized\f[R] +And this is \f[B]strong\f[R] .PP Here’s a simple block: .LP @@ -621,29 +621,29 @@ Inline Markup .pdfhref O 1 "Inline Markup" .pdfhref M "inline-markup" .LP -This is \f[I]emphasized\f[], and so \f[I]is this\f[]. +This is \f[I]emphasized\f[R], and so \f[I]is this\f[R]. .PP -This is \f[B]strong\f[], and so \f[B]is this\f[]. +This is \f[B]strong\f[R], and so \f[B]is this\f[R]. .PP An \f[I]\c .pdfhref W -D "/url" -A "\c" \ -- "emphasized link" -\&\f[]. +\&\f[R]. .PP -\f[B]\f[BI]This is strong and em.\f[B]\f[] +\f[B]\f[BI]This is strong and em.\f[B]\f[R] .PP -So is \f[B]\f[BI]this\f[B]\f[] word. +So is \f[B]\f[BI]this\f[B]\f[R] word. .PP -\f[B]\f[BI]This is strong and em.\f[B]\f[] +\f[B]\f[BI]This is strong and em.\f[B]\f[R] .PP -So is \f[B]\f[BI]this\f[B]\f[] word. +So is \f[B]\f[BI]this\f[B]\f[R] word. .PP -This is code: \f[C]>\f[], \f[C]$\f[], \f[C]\\\f[], \f[C]\\$\f[], -\f[C]\f[]. +This is code: \f[C]>\f[R], \f[C]$\f[R], \f[C]\\\f[R], \f[C]\\$\f[R], +\f[C]\f[R]. .PP -\m[strikecolor]This is \f[I]strikeout\f[].\m[] +\m[strikecolor]This is \f[I]strikeout\f[R].\m[] .PP -Superscripts: a\*{bc\*}d a\*{\f[I]hello\f[]\*} a\*{hello\~there\*}. +Superscripts: a\*{bc\*}d a\*{\f[I]hello\f[R]\*} a\*{hello\~there\*}. .PP Subscripts: H\*<2\*>O, H\*<23\*>O, H\*O. .PP @@ -665,7 +665,7 @@ So is `pine.' .PP `He said, \[lq]I want to go.\[rq]' Were you alive in the 70’s? .PP -Here is some quoted `\f[C]code\f[]' and a \[lq]\c +Here is some quoted `\f[C]code\f[R]' and a \[lq]\c .pdfhref W -D "http://example.com/?foo=1&bar=2" -A "\c" \ -- "quoted link" \&\[rq]. @@ -701,15 +701,15 @@ Here’s one that has a line break in it: @alpha + omega times x sup 2@. .LP These shouldn’t be math: .IP \[bu] 3 -To get the famous equation, write \f[C]$e\ =\ mc\[ha]2$\f[]. +To get the famous equation, write \f[C]$e\ =\ mc\[ha]2$\f[R]. .IP \[bu] 3 -$22,000 is a \f[I]lot\f[] of money. +$22,000 is a \f[I]lot\f[R] of money. So is $34,000. (It worked if \[lq]lot\[rq] is emphasized.) .IP \[bu] 3 Shoes ($20) and socks ($5). .IP \[bu] 3 -Escaped \f[C]$\f[]: $73 \f[I]this should be emphasized\f[] 23$. +Escaped \f[C]$\f[R]: $73 \f[I]this should be emphasized\f[R] 23$. .LP Here’s a LaTeX table: .HLINE @@ -932,7 +932,7 @@ Blockquoted: \c \& .RE .LP -Auto-links should not occur here: \f[C]\f[] +Auto-links should not occur here: \f[C]\f[R] .IP .nf \f[C] @@ -979,14 +979,14 @@ with list items). If you want, you can indent every line, but you can also be lazy and just indent the first line of each block. .FE -This should \f[I]not\f[] be a footnote reference, because it contains a +This should \f[I]not\f[R] be a footnote reference, because it contains a space.[\[ha]my note] Here is an inline note.\** .FS -This is \f[I]easier\f[] to type. +This is \f[I]easier\f[R] to type. Inline notes may contain \c .pdfhref W -D "http://google.com" -A "\c" \ -- "links" -\& and \f[C]]\f[] verbatim characters, as well as [bracketed text]. +\& and \f[C]]\f[R] verbatim characters, as well as [bracketed text]. .FE .RS .LP -- cgit v1.2.3 From f39931fd6c86a4bf7a651f9e2f5667bfad99bcca Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Mon, 16 Apr 2018 11:40:18 +0300 Subject: Muse writer: escape definition list terms starting with list markers --- src/Text/Pandoc/Writers/Muse.hs | 13 +++++++------ test/Tests/Writers/Muse.hs | 9 +++++++++ 2 files changed, 16 insertions(+), 6 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 4e7ce377a..d1e407026 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -101,7 +101,7 @@ writeMuse opts document = , envInsideBlock = False , envInlineStart = True , envInsideLinkDescription = False - , envAfterSpace = True + , envAfterSpace = False , envOneLine = False } @@ -223,7 +223,7 @@ blockToMuse (DefinitionList items) = do => ([Inline], [[Block]]) -> Muse m Doc definitionListItemToMuse (label, defs) = do - label' <- local (\env -> env { envOneLine = True }) $ inlineListToMuse' label + label' <- local (\env -> env { envOneLine = True, envAfterSpace = True }) $ inlineListToMuse' label contents <- vcat <$> mapM descriptionToMuse defs let ind = offset label' return $ hang ind label' contents @@ -439,14 +439,15 @@ renderInlineList (x:xs) = do -- | Normalize and convert list of Pandoc inline elements to Muse. inlineListToMuse'' :: PandocMonad m - => Bool - -> [Inline] - -> Muse m Doc + => Bool + -> [Inline] + -> Muse m Doc inlineListToMuse'' start lst = do lst' <- (normalizeInlineList . fixNotes) <$> preprocessInlineList (map (removeKeyValues . replaceSmallCaps) lst) topLevel <- asks envTopLevel + afterSpace <- asks envAfterSpace local (\env -> env { envInlineStart = start - , envAfterSpace = start && not topLevel + , envAfterSpace = afterSpace || (start && not topLevel) }) $ renderInlineList lst' inlineListToMuse' :: PandocMonad m => [Inline] -> Muse m Doc diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index 44fdd5b7e..ff66d1d65 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -121,6 +121,15 @@ tests = [ testGroup "block elements" , " foo :: second description" , " > bar :: third description" ] + , "definition list terms starting with list markers" =: + definitionList [ (text "first definition", [plain $ text "first description"]) + , (str "-", [plain $ text "second description"]) + , (str "1.", [plain $ text "third description"]) + ] + =?> unlines [ " first definition :: first description" + , " - :: second description" + , " 1. :: third description" + ] ] -- Test that lists of the same type and style are separated with two blanklines , testGroup "sequential lists" -- cgit v1.2.3 From fb014e6e9f601fef026019a9822ff1c19f24de45 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Mon, 16 Apr 2018 12:42:39 +0300 Subject: Muse reader code cleanup --- src/Text/Pandoc/Readers/Muse.hs | 29 +++++++++-------------------- 1 file changed, 9 insertions(+), 20 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs index c417588b8..1ba4ac343 100644 --- a/src/Text/Pandoc/Readers/Muse.hs +++ b/src/Text/Pandoc/Readers/Muse.hs @@ -572,10 +572,8 @@ bulletListItemsUntil indent end = try $ do char '-' void spaceChar <|> lookAhead eol updateState (\st -> st { museInPara = False }) - (x, e) <- listItemContentsUntil (indent + 2) (Right <$> try (optional blankline >> indentWith indent >> bulletListItemsUntil indent end)) (Left <$> end) - case e of - Left ee -> return ([x], ee) - Right (xs, ee) -> return (x:xs, ee) + (x, (xs, e)) <- listItemContentsUntil (indent + 2) (try (optional blankline >> indentWith indent >> bulletListItemsUntil indent end)) (([],) <$> end) + return (x:xs, e) -- | Parse a bullet list. bulletListUntil :: PandocMonad m @@ -621,10 +619,8 @@ orderedListItemsUntil indent style end = pos <- getPosition void spaceChar <|> lookAhead eol updateState (\st -> st { museInPara = False }) - (x, e) <- listItemContentsUntil (sourceColumn pos) (Right <$> try (optional blankline >> indentWith indent >> museOrderedListMarker style >> continuation)) (Left <$> end) - case e of - Left ee -> return ([x], ee) - Right (xs, ee) -> return (x:xs, ee) + (x, (xs, e)) <- listItemContentsUntil (sourceColumn pos) (try (optional blankline >> indentWith indent >> museOrderedListMarker style >> continuation)) (([],) <$> end) + return (x:xs, e) -- | Parse an ordered list. orderedListUntil :: PandocMonad m @@ -647,10 +643,8 @@ descriptionsUntil :: PandocMonad m descriptionsUntil indent end = do void spaceChar <|> lookAhead eol updateState (\st -> st { museInPara = False }) - (x, e) <- listItemContentsUntil indent (Right <$> try (optional blankline >> indentWith indent >> manyTill spaceChar (string "::") >> descriptionsUntil indent end)) (Left <$> end) - case e of - Right (xs, ee) -> return (x:xs, ee) - Left ee -> return ([x], ee) + (x, (xs, e)) <- listItemContentsUntil indent (try (optional blankline >> indentWith indent >> manyTill spaceChar (string "::") >> descriptionsUntil indent end)) (([],) <$> end) + return (x:xs, e) definitionListItemsUntil :: PandocMonad m => Int @@ -662,14 +656,9 @@ definitionListItemsUntil indent end = continuation = try $ do pos <- getPosition term <- trimInlinesF . mconcat <$> manyTill (choice inlineList) (try $ string "::") - (x, e) <- descriptionsUntil (sourceColumn pos) ((Right <$> try (optional blankline >> indentWith indent >> continuation)) <|> (Left <$> end)) - let xx = do - term' <- term - x' <- sequence x - return (term', x') - case e of - Left ee -> return ([xx], ee) - Right (xs, ee) -> return (xx:xs, ee) + (x, (xs, e)) <- descriptionsUntil (sourceColumn pos) (try (optional blankline >> indentWith indent >> continuation) <|> (([],) <$> end)) + let xx = (,) <$> term <*> sequence x + return (xx:xs, e) -- | Parse a definition list. definitionListUntil :: PandocMonad m -- cgit v1.2.3 From a8122987fc3301bc6c0b799312cc2f676bec8042 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Mon, 16 Apr 2018 15:08:34 +0300 Subject: Muse reader: allow verse to be indented Muse writer indents verse blocks in definition list more than necessary, so Muse reader should parse them. --- src/Text/Pandoc/Readers/Muse.hs | 1 + test/Tests/Readers/Muse.hs | 18 ++++++++++++++++++ 2 files changed, 19 insertions(+) (limited to 'src') diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs index 1ba4ac343..98c1a9d55 100644 --- a/src/Text/Pandoc/Readers/Muse.hs +++ b/src/Text/Pandoc/Readers/Muse.hs @@ -558,6 +558,7 @@ blanklineVerseLine = try $ do -- | Parse a line block indicated by @\'>\'@ characters. lineBlock :: PandocMonad m => MuseParser m (F Blocks) lineBlock = try $ do + many spaceChar col <- sourceColumn <$> getPosition lns <- (blanklineVerseLine <|> lineVerseLine) `sepBy1'` try (indentWith (col - 1)) return $ B.lineBlock <$> sequence lns diff --git a/test/Tests/Readers/Muse.hs b/test/Tests/Readers/Muse.hs index 86f0d7888..8474b2509 100644 --- a/test/Tests/Readers/Muse.hs +++ b/test/Tests/Readers/Muse.hs @@ -1153,6 +1153,24 @@ tests = definitionList [ ("First term", [ para "Definition of first term\nand its continuation." ]) , ("Second term", [ para "Definition of second term." ]) ] + , "Definition list with verse" =: + T.unlines + [ " First term :: Definition of first term" + , " > First verse" + , " > Second line of first verse" + , "" + , " > Second verse" + , " > Second line of second verse" + ] =?> + definitionList [ ("First term", [ para "Definition of first term" <> + lineBlock [ text "First verse" + , text "Second line of first verse" + ] <> + lineBlock [ text "Second verse" + , text "Second line of second verse" + ] + ]) + ] , test emacsMuse "Multi-line definition lists from Emacs Muse manual" (T.unlines [ "Term1 ::" -- cgit v1.2.3 From 46cc1e73b63c7046d7311cb4551bcc1794af41a8 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Mon, 16 Apr 2018 15:36:30 +0300 Subject: Muse writer: simplify isHorizontalRule --- src/Text/Pandoc/Writers/Muse.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index d1e407026..17ca727c1 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -396,9 +396,7 @@ urlEscapeBrackets (x:xs) = x:urlEscapeBrackets xs urlEscapeBrackets [] = [] isHorizontalRule :: String -> Bool -isHorizontalRule s = - ((length xs) >= 4) && null ys - where (xs, ys) = span (== '-') s +isHorizontalRule s = length s >= 4 && all (== '-') s startsWithSpace :: String -> Bool startsWithSpace (x:_) = isSpace x -- cgit v1.2.3 From 04478cf0e2930b00d962bcb55b28bc26889fd049 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Mon, 16 Apr 2018 16:03:49 +0300 Subject: hlint Muse writer --- src/Text/Pandoc/Writers/Muse.hs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 17ca727c1..6ed6ed1ca 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -87,7 +87,7 @@ instance Default WriterState } evalMuse :: PandocMonad m => Muse m a -> WriterEnv -> WriterState -> m a -evalMuse document env st = evalStateT (runReaderT document env) st +evalMuse document env = evalStateT $ runReaderT document env -- | Convert Pandoc to Muse. writeMuse :: PandocMonad m @@ -276,7 +276,7 @@ blockToMuse Null = return empty notesToMuse :: PandocMonad m => Notes -> Muse m Doc -notesToMuse notes = vsep <$> (zipWithM noteToMuse [1 ..] notes) +notesToMuse notes = vsep <$> zipWithM noteToMuse [1 ..] notes -- | Return Muse representation of a note. noteToMuse :: PandocMonad m @@ -307,8 +307,7 @@ startsWithMarker _ [] = False -- | Escape special characters for Muse if needed. containsFootnotes :: String -> Bool -containsFootnotes st = - p st +containsFootnotes = p where p ('[':xs) = q xs || p xs p (_:xs) = p xs p "" = False -- cgit v1.2.3 From 57256d6d91669d1a0256132cd9336364656eb924 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Mon, 16 Apr 2018 19:02:49 -0700 Subject: Beamer writer: don't use format specifier for default ordered lists. This gives better results for styles that put ordered list markers in boxes or circles. Closes #4556. --- src/Text/Pandoc/Writers/LaTeX.hs | 1 + 1 file changed, 1 insertion(+) (limited to 'src') diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index f354bc0a2..d9868b7cd 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -678,6 +678,7 @@ blockToLaTeX (OrderedList (start, numstyle, numdelim) lst) = do let enum = text $ "enum" ++ map toLower (toRomanNumeral oldlevel) let stylecommand | numstyle == DefaultStyle && numdelim == DefaultDelim = empty + | beamer && numstyle == Decimal && numdelim == Period = empty | beamer = brackets (todelim exemplar) | otherwise = "\\def" <> "\\label" <> enum <> braces (todelim $ tostyle enum) -- cgit v1.2.3 From 8ac5eb9d44cb15547dfdcfc01e46c9ca49b400b9 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Mon, 16 Apr 2018 23:15:09 -0700 Subject: Markdown reader: remove "fallback" for doubleQuote parser. Previously the parser tried to be efficient -- if no end double quote was found, it would just return the contents. But this could backfire in a case like: **this should "be bold** since the fallback would return the content `"be bold**` and the closing boldface delimiter would never be encountered. --- src/Text/Pandoc/Readers/Markdown.hs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 71e6f8249..fb42612ca 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -2146,7 +2146,6 @@ singleQuoted = try $ do doubleQuoted :: PandocMonad m => MarkdownParser m (F Inlines) doubleQuoted = try $ do doubleQuoteStart - contents <- mconcat <$> many (try $ notFollowedBy doubleQuoteEnd >> inline) - withQuoteContext InDoubleQuote (doubleQuoteEnd >> return - (fmap B.doubleQuoted . trimInlinesF $ contents)) - <|> return (return (B.str "\8220") <> contents) + withQuoteContext InDoubleQuote $ + fmap B.doubleQuoted . trimInlinesF . mconcat <$> + many1Till inline doubleQuoteEnd -- cgit v1.2.3 From b948ca6db2a02b73aae1f77535cc592fc7b80974 Mon Sep 17 00:00:00 2001 From: Jesse Rosenthal Date: Tue, 17 Apr 2018 09:08:28 -0400 Subject: Docx reader: Combine codeBlocks This prevents a multiline codeblock in word from being read as different paragraphs. This takes place in the Combine module to occur during the normal combining of divs during conversion. Note that this specifies that the attributes of the `CodeBlock`s must be the same. The docx reader creates codeBlocks without attrs, so this is trivially satisified. --- src/Text/Pandoc/Readers/Docx/Combine.hs | 4 ++++ 1 file changed, 4 insertions(+) (limited to 'src') diff --git a/src/Text/Pandoc/Readers/Docx/Combine.hs b/src/Text/Pandoc/Readers/Docx/Combine.hs index dfd2b5666..108c4bbe5 100644 --- a/src/Text/Pandoc/Readers/Docx/Combine.hs +++ b/src/Text/Pandoc/Readers/Docx/Combine.hs @@ -135,6 +135,10 @@ combineBlocks bs cs | bs' :> BlockQuote bs'' <- viewr (unMany bs) , BlockQuote cs'' :< cs' <- viewl (unMany cs) = Many $ (bs' |> BlockQuote (bs'' <> cs'')) >< cs' + | bs' :> CodeBlock attr codeStr <- viewr (unMany bs) + , CodeBlock attr' codeStr' :< cs' <- viewl (unMany cs) + , attr == attr' = + Many $ (bs' |> CodeBlock attr (codeStr <> "\n" <> codeStr')) >< cs' combineBlocks bs cs = bs <> cs instance (Monoid a, Eq a) => Eq (Modifier a) where -- cgit v1.2.3 From bc9d296e5ae34f14cc03d7ca5e3b1f4295eac1d2 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 18 Apr 2018 18:27:15 -0700 Subject: Markdown reader: handle table w/o following blank line in fenced div. Closes #4560. --- src/Text/Pandoc/Readers/Markdown.hs | 17 ++++++++++++++--- 1 file changed, 14 insertions(+), 3 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index fb42612ca..3a1346fdc 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -910,6 +910,17 @@ listContinuation continuationIndent = try $ do blanks <- many blankline return $ concat (x:xs) ++ blanks +-- Variant of blanklines that doesn't require blank lines +-- before a fence or eof. +blanklines' :: PandocMonad m => MarkdownParser m [Char] +blanklines' = blanklines <|> try checkDivCloser + where checkDivCloser = do + guardEnabled Ext_fenced_divs + divLevel <- stateFencedDivLevel <$> getState + guard (divLevel >= 1) + lookAhead divFenceEnd + return "" + notFollowedByDivCloser :: PandocMonad m => MarkdownParser m () notFollowedByDivCloser = guardDisabled Ext_fenced_divs <|> @@ -1251,7 +1262,7 @@ alignType strLst len = -- Parse a table footer - dashed lines followed by blank line. tableFooter :: PandocMonad m => MarkdownParser m String -tableFooter = try $ skipNonindentSpaces >> many1 (dashedLine '-') >> blanklines +tableFooter = try $ skipNonindentSpaces >> many1 (dashedLine '-') >> blanklines' -- Parse a table separator - dashed line. tableSep :: PandocMonad m => MarkdownParser m Char @@ -1262,7 +1273,7 @@ rawTableLine :: PandocMonad m => [Int] -> MarkdownParser m [String] rawTableLine indices = do - notFollowedBy' (blanklines <|> tableFooter) + notFollowedBy' (blanklines' <|> tableFooter) line <- many1Till anyChar newline return $ map trim $ tail $ splitStringByIndices (init indices) line @@ -1300,7 +1311,7 @@ simpleTable headless = do (aligns, _widths, heads', lines') <- tableWith (simpleTableHeader headless) tableLine (return ()) - (if headless then tableFooter else tableFooter <|> blanklines) + (if headless then tableFooter else tableFooter <|> blanklines') -- Simple tables get 0s for relative column widths (i.e., use default) return (aligns, replicate (length aligns) 0, heads', lines') -- cgit v1.2.3 From ce4326a4f12180844532febf93261f098cd6c5aa Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Thu, 19 Apr 2018 14:17:59 +0300 Subject: Muse reader: allow "-" in anchors --- src/Text/Pandoc/Readers/Muse.hs | 2 +- test/Tests/Readers/Muse.hs | 5 +++++ 2 files changed, 6 insertions(+), 1 deletion(-) (limited to 'src') diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs index 98c1a9d55..43c835edb 100644 --- a/src/Text/Pandoc/Readers/Muse.hs +++ b/src/Text/Pandoc/Readers/Muse.hs @@ -801,7 +801,7 @@ parseAnchor :: PandocMonad m => MuseParser m String parseAnchor = try $ do getPosition >>= \pos -> guard (sourceColumn pos == 1) char '#' - (:) <$> letter <*> many (letter <|> digit) + (:) <$> letter <*> many (letter <|> digit <|> char '-') anchor :: PandocMonad m => MuseParser m (F Inlines) anchor = try $ do diff --git a/test/Tests/Readers/Muse.hs b/test/Tests/Readers/Muse.hs index 8474b2509..a7eb9d0eb 100644 --- a/test/Tests/Readers/Muse.hs +++ b/test/Tests/Readers/Muse.hs @@ -637,6 +637,11 @@ tests = , "#anchor and ends here." ] =?> para ("Paragraph starts here\n" <> spanWith ("anchor", [], []) mempty <> "and ends here.") + , "Anchor with \"-\"" =: + T.unlines [ "; A comment to make sure anchor is not parsed as a directive" + , "#anchor-id Target" + ] =?> + para (spanWith ("anchor-id", [], []) mempty <> "Target") ] , testGroup "Footnotes" [ "Simple footnote" =: -- cgit v1.2.3 From caeb963447440edb14a67bb02cb6c956232dce63 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Thu, 19 Apr 2018 17:03:21 +0300 Subject: FB2 writer: convert metadata value "abstract" to book annotation --- src/Text/Pandoc/Writers/FB2.hs | 5 ++++- test/Tests/Old.hs | 1 + test/fb2/meta.fb2 | 3 +++ test/fb2/meta.markdown | 7 +++++++ 4 files changed, 15 insertions(+), 1 deletion(-) create mode 100644 test/fb2/meta.fb2 create mode 100644 test/fb2/meta.markdown (limited to 'src') diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index f0d2cc3af..e1fa7f474 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -118,6 +118,9 @@ description meta' = do bt <- booktitle meta' let as = authors meta' dd <- docdate meta' + annotation <- case lookupMeta "abstract" meta' of + Just (MetaBlocks bs) -> (list . el "annotation") <$> cMapM blockToXml bs + _ -> pure mempty let lang = case lookupMeta "lang" meta' of Just (MetaInlines [Str s]) -> [el "lang" $ iso639 s] Just (MetaString s) -> [el "lang" $ iso639 s] @@ -132,7 +135,7 @@ description meta' = do Just (MetaString s) -> coverimage s _ -> return [] return $ el "description" - [ el "title-info" (genre : (bt ++ as ++ dd ++ lang)) + [ el "title-info" (genre : (bt ++ annotation ++ as ++ dd ++ lang)) , el "document-info" (el "program-used" "pandoc" : coverpage) ] diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs index f2b43640b..cfca576da 100644 --- a/test/Tests/Old.hs +++ b/test/Tests/Old.hs @@ -95,6 +95,7 @@ tests = [ testGroup "markdown" , fb2WriterTest "images" [] "fb2/images.markdown" "fb2/images.fb2" , fb2WriterTest "images-embedded" [] "fb2/images-embedded.html" "fb2/images-embedded.fb2" , fb2WriterTest "math" [] "fb2/math.markdown" "fb2/math.fb2" + , fb2WriterTest "meta" [] "fb2/meta.markdown" "fb2/meta.fb2" , fb2WriterTest "tables" [] "tables.native" "tables.fb2" , fb2WriterTest "testsuite" [] "testsuite.native" "writer.fb2" ] diff --git a/test/fb2/meta.fb2 b/test/fb2/meta.fb2 new file mode 100644 index 000000000..04bd5f3c5 --- /dev/null +++ b/test/fb2/meta.fb2 @@ -0,0 +1,3 @@ + +unrecognisedBook title

This is the abstract.

It consists of two paragraphs.
pandoc
<p>Book title</p>
+ diff --git a/test/fb2/meta.markdown b/test/fb2/meta.markdown new file mode 100644 index 000000000..5edad2981 --- /dev/null +++ b/test/fb2/meta.markdown @@ -0,0 +1,7 @@ +--- +title: Book title +abstract: | + This is the abstract. + + It consists of two paragraphs. +--- -- cgit v1.2.3 From b87dd19816f193e895dfc403a8b5a860d0e48d7d Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 19 Apr 2018 11:35:26 -0700 Subject: EPUB reader: fix images with space in file path. Closes #4344. --- src/Text/Pandoc/Readers/EPUB.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Readers/EPUB.hs b/src/Text/Pandoc/Readers/EPUB.hs index 714468a8a..5c92c188b 100644 --- a/src/Text/Pandoc/Readers/EPUB.hs +++ b/src/Text/Pandoc/Readers/EPUB.hs @@ -93,7 +93,7 @@ fetchImages mimes root arc (query iq -> links) = mapM_ (uncurry3 insertMedia) (mapMaybe getEntry links) where getEntry link = - let abslink = normalise (root link) in + let abslink = normalise (unEscapeString (root link)) in (link , lookup link mimes, ) . fromEntry <$> findEntryByPath abslink arc @@ -264,7 +264,7 @@ findAttrE :: PandocMonad m => QName -> Element -> m String findAttrE q e = mkE "findAttr" $ findAttr q e findEntryByPathE :: PandocMonad m => FilePath -> Archive -> m Entry -findEntryByPathE (normalise -> path) a = +findEntryByPathE (normalise . unEscapeString -> path) a = mkE ("No entry on path: " ++ path) $ findEntryByPath path a parseXMLDocE :: PandocMonad m => String -> m Element -- cgit v1.2.3 From b15f4f468dd9d50c60eeea982048730200a2858b Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 19 Apr 2018 11:39:35 -0700 Subject: Text.Pandoc.Class.writeMedia: unescape URI-escaping in file path. This avoids writing things like `file%20one.png` to the file system. --- src/Text/Pandoc/Class.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) (limited to 'src') diff --git a/src/Text/Pandoc/Class.hs b/src/Text/Pandoc/Class.hs index c78822ee9..3529054e6 100644 --- a/src/Text/Pandoc/Class.hs +++ b/src/Text/Pandoc/Class.hs @@ -855,7 +855,7 @@ writeMedia :: FilePath -> MediaBag -> FilePath -> PandocIO () writeMedia dir mediabag subpath = do -- we join and split to convert a/b/c to a\b\c on Windows; -- in zip containers all paths use / - let fullpath = dir normalise subpath + let fullpath = dir unEscapeString (normalise subpath) let mbcontents = lookupMedia subpath mediabag case mbcontents of Nothing -> throwError $ PandocResourceNotFound subpath -- cgit v1.2.3 From c76565bef5ecdbf1173d23b79dda59df4120cdb9 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 19 Apr 2018 11:49:17 -0700 Subject: Parsing.uri: don't treat `*` characters at end as part of URI. This fixes #4561, a bug parsing emphasized bare links in RST. --- src/Text/Pandoc/Parsing.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) (limited to 'src') diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index 1fab1bf72..fa6baf1c7 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -593,7 +593,7 @@ uri = try $ do -- http://en.wikipedia.org/wiki/State_of_emergency_(disambiguation) -- as a URL, while NOT picking up the closing paren in -- (http://wikipedia.org). So we include balanced parens in the URL. - let isWordChar c = isAlphaNum c || c `elem` "#$%*+/@\\_-&=" + let isWordChar c = isAlphaNum c || c `elem` "#$%+/@\\_-&=" let wordChar = satisfy isWordChar let percentEscaped = try $ char '%' >> skipMany1 (satisfy isHexDigit) let entity = () <$ characterReference -- cgit v1.2.3 From 276894a2f2f7421c3470a4d50af94774ebef62d7 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 19 Apr 2018 13:47:16 -0700 Subject: RST writer: use more consistent indentation. Previously we used an odd mix of 3- and 4-space indentation. Now we use 3-space indentation, except for ordered lists, where indentation must depend on the width of the list marker. Closes #4563. --- src/Text/Pandoc/Writers/RST.hs | 9 ++-- test/Tests/Writers/RST.hs | 18 +++---- test/command/3675.md | 4 +- test/command/4320.md | 10 ++-- test/lhs-test.rst | 10 ++-- test/lhs-test.rst+lhs | 4 +- test/writer.rst | 120 ++++++++++++++++++++--------------------- 7 files changed, 86 insertions(+), 89 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 74fc4dca4..cc7131d0a 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -263,7 +263,6 @@ blockToRST (Header level (name,classes,_) inlines) = do return $ nowrap $ hang 3 ".. " (rub $$ name' $$ cls) $$ blankline blockToRST (CodeBlock (_,classes,kvs) str) = do opts <- gets stOptions - let tabstop = writerTabStop opts let startnum = maybe "" (\x -> " " <> text x) $ lookup "startFrom" kvs let numberlines = if "numberLines" `elem` classes then " :number-lines:" <> startnum @@ -276,11 +275,10 @@ blockToRST (CodeBlock (_,classes,kvs) str) = do c `notElem` ["sourceCode","literate","numberLines"]] of [] -> "::" (lang:_) -> (".. code:: " <> text lang) $$ numberlines) - $+$ nest tabstop (text str) $$ blankline + $+$ nest 3 (text str) $$ blankline blockToRST (BlockQuote blocks) = do - tabstop <- gets $ writerTabStop . stOptions contents <- blockListToRST blocks - return $ nest tabstop contents <> blankline + return $ nest 3 contents <> blankline blockToRST (Table caption aligns widths headers rows) = do caption' <- inlineListToRST caption let blocksToDoc opts bs = do @@ -338,8 +336,7 @@ definitionListItemToRST :: PandocMonad m => ([Inline], [[Block]]) -> RST m Doc definitionListItemToRST (label, defs) = do label' <- inlineListToRST label contents <- liftM vcat $ mapM blockListToRST defs - tabstop <- gets $ writerTabStop . stOptions - return $ nowrap label' $$ nest tabstop (nestle contents <> cr) + return $ nowrap label' $$ nest 3 (nestle contents <> cr) -- | Format a list of lines as line block. linesToLineBlock :: PandocMonad m => [[Inline]] -> RST m Doc diff --git a/test/Tests/Writers/RST.hs b/test/Tests/Writers/RST.hs index 64367a108..29c9328f6 100644 --- a/test/Tests/Writers/RST.hs +++ b/test/Tests/Writers/RST.hs @@ -24,23 +24,23 @@ tests = [ testGroup "rubrics" para $ text "baz"])] =?> unlines [ "foo" - , " .. rubric:: bar" + , " .. rubric:: bar" , "" - , " baz"] + , " baz"] , "in block quote" =: blockQuote (header 1 (text "bar")) =?> - " .. rubric:: bar" + " .. rubric:: bar" , "with id" =: blockQuote (headerWith ("foo",[],[]) 1 (text "bar")) =?> unlines - [ " .. rubric:: bar" - , " :name: foo"] + [ " .. rubric:: bar" + , " :name: foo"] , "with id class" =: blockQuote (headerWith ("foo",["baz"],[]) 1 (text "bar")) =?> unlines - [ " .. rubric:: bar" - , " :name: foo" - , " :class: baz"] + [ " .. rubric:: bar" + , " :name: foo" + , " :class: baz"] ] , testGroup "ligatures" -- handling specific sequences of blocks [ "a list is closed by a comment before a quote" =: -- issue 4248 @@ -50,7 +50,7 @@ tests = [ testGroup "rubrics" , "" , ".." , "" - , " quoted"] + , " quoted"] ] , testGroup "inlines" [ "are removed when empty" =: -- #4434 diff --git a/test/command/3675.md b/test/command/3675.md index b129c7a63..f75721b56 100644 --- a/test/command/3675.md +++ b/test/command/3675.md @@ -7,9 +7,9 @@ print("hello") ^D .. code:: python - print("hello") + print("hello") .. - block quote + block quote ```` diff --git a/test/command/4320.md b/test/command/4320.md index 5b0eeb5c1..732b30a3e 100644 --- a/test/command/4320.md +++ b/test/command/4320.md @@ -7,9 +7,9 @@ ,[BlockQuote [Para [Strong [Str "thisIsGoingToBeTooLongAnyway"]]]]]]] ^D -+-------+--------------------------------------+ -| one | two | -+=======+======================================+ -| ports | **thisIsGoingToBeTooLongAnyway** | -+-------+--------------------------------------+ ++-------+-------------------------------------+ +| one | two | ++=======+=====================================+ +| ports | **thisIsGoingToBeTooLongAnyway** | ++-------+-------------------------------------+ ``` diff --git a/test/lhs-test.rst b/test/lhs-test.rst index 3de2d9ff6..4d012a9f9 100644 --- a/test/lhs-test.rst +++ b/test/lhs-test.rst @@ -6,9 +6,9 @@ return a single value: .. code:: haskell - unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d - unsplit = arr . uncurry - -- arr (\op (x,y) -> x `op` y) + unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d + unsplit = arr . uncurry + -- arr (\op (x,y) -> x `op` y) ``(***)`` combines two arrows into a new arrow by running the two arrows on a pair of values (one arrow on the first item of the pair and one arrow on the @@ -16,8 +16,8 @@ second item of the pair). :: - f *** g = first f >>> second g + f *** g = first f >>> second g Block quote: - foo bar + foo bar diff --git a/test/lhs-test.rst+lhs b/test/lhs-test.rst+lhs index eec79c546..6196c39ab 100644 --- a/test/lhs-test.rst+lhs +++ b/test/lhs-test.rst+lhs @@ -14,8 +14,8 @@ second item of the pair). :: - f *** g = first f >>> second g + f *** g = first f >>> second g Block quote: - foo bar + foo bar diff --git a/test/writer.rst b/test/writer.rst index 93158f0c3..3353d11d3 100644 --- a/test/writer.rst +++ b/test/writer.rst @@ -69,30 +69,30 @@ Block Quotes E-mail style: - This is a block quote. It is pretty short. + This is a block quote. It is pretty short. .. - Code in a block quote: + Code in a block quote: - :: + :: - sub status { - print "working"; - } + sub status { + print "working"; + } - A list: + A list: - 1. item one - 2. item two + 1. item one + 2. item two - Nested block quotes: + Nested block quotes: - nested + nested - .. + .. - nested + nested This should not be a block quote: 2 > 1. @@ -107,21 +107,21 @@ Code: :: - ---- (should be four hyphens) + ---- (should be four hyphens) - sub status { - print "working"; - } + sub status { + print "working"; + } - this code block is indented by one tab + this code block is indented by one tab And: :: - this code block is indented by two tabs + this code block is indented by two tabs - These should not be escaped: \$ \\ \> \[ \{ + These should not be escaped: \$ \\ \> \[ \{ -------------- @@ -302,83 +302,83 @@ Definition Lists Tight using spaces: apple - red fruit + red fruit orange - orange fruit + orange fruit banana - yellow fruit + yellow fruit Tight using tabs: apple - red fruit + red fruit orange - orange fruit + orange fruit banana - yellow fruit + yellow fruit Loose: apple - red fruit + red fruit orange - orange fruit + orange fruit banana - yellow fruit + yellow fruit Multiple blocks with italics: *apple* - red fruit + red fruit - contains seeds, crisp, pleasant to taste + contains seeds, crisp, pleasant to taste *orange* - orange fruit + orange fruit - :: + :: - { orange code block } + { orange code block } - .. + .. - orange block quote + orange block quote Multiple definitions, tight: apple - red fruit - computer + red fruit + computer orange - orange fruit - bank + orange fruit + bank Multiple definitions, loose: apple - red fruit + red fruit - computer + computer orange - orange fruit + orange fruit - bank + bank Blank line after term, indented marker, alternate markers: apple - red fruit + red fruit - computer + computer orange - orange fruit + orange fruit - 1. sublist - 2. sublist + 1. sublist + 2. sublist HTML Blocks =========== @@ -491,15 +491,15 @@ This should be a code block, though: :: -
- foo -
+
+ foo +
As should this: :: -
foo
+
foo
Now, nested: @@ -554,7 +554,7 @@ Code block: :: - + Just plain comment, with trailing spaces on the line: @@ -566,7 +566,7 @@ Code: :: -
+
Hr’s: @@ -793,7 +793,7 @@ This should [not][] be a link. :: - [not]: /url + [not]: /url Foo `bar `__. @@ -822,13 +822,13 @@ With an ampersand: http://example.com/?foo=1&bar=2 An e-mail address: nobody@nowhere.net - Blockquoted: http://example.com/ + Blockquoted: http://example.com/ Auto-links should not occur here: ```` :: - or here: + or here: -------------- @@ -853,7 +853,7 @@ Here is a footnote reference, [1]_ and another. [2]_ This should *not* be a footnote reference, because it contains a space.[^my note] Here is an inline note. [3]_ - Notes can go in quotes. [4]_ + Notes can go in quotes. [4]_ 1. And in list items. [5]_ @@ -871,7 +871,7 @@ This paragraph should not be part of the note, as it is not indented. :: - { } + { } If you want, you can indent every line, but you can also be lazy and just indent the first line of each block. -- cgit v1.2.3 From f508c833f163f25b5ca203b96876f277dd927282 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 19 Apr 2018 23:01:52 -0700 Subject: Markdown reader: allow empty attributes. See #2944. --- src/Text/Pandoc/Readers/Markdown.hs | 2 ++ 1 file changed, 2 insertions(+) (limited to 'src') diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 3a1346fdc..0d1a83bab 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -674,6 +674,8 @@ keyValAttr = try $ do char '=' val <- enclosed (char '"') (char '"') litChar <|> enclosed (char '\'') (char '\'') litChar + <|> ("" <$ try (string "\"\"")) + <|> ("" <$ try (string "''")) <|> many (escapedChar' <|> noneOf " \t\n\r}") return $ \(id',cs,kvs) -> case key of -- cgit v1.2.3 From ec30d56e1948166a979a33b1befade3cd37fbd82 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 21 Apr 2018 12:11:48 -0700 Subject: Mime: Use the alias application/eps for eps. Instead of application/postscript. This will ensure that we retain the eps extension after reading the image into a mediabag and writing it again. See #2067. --- src/Text/Pandoc/MIME.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) (limited to 'src') diff --git a/src/Text/Pandoc/MIME.hs b/src/Text/Pandoc/MIME.hs index 2f37c1b83..cb7debb2e 100644 --- a/src/Text/Pandoc/MIME.hs +++ b/src/Text/Pandoc/MIME.hs @@ -174,7 +174,7 @@ mimeTypesList = -- List borrowed from happstack-server. ,("eml","message/rfc822") ,("ent","chemical/x-ncbi-asn1-ascii") ,("eot","application/vnd.ms-fontobject") - ,("eps","application/postscript") + ,("eps","application/eps") ,("etx","text/x-setext") ,("exe","application/x-msdos-program") ,("ez","application/andrew-inset") -- cgit v1.2.3 From cd51983afe08697d627ecb091d42e40d897470b9 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 21 Apr 2018 12:27:30 -0700 Subject: makePDF: For pdflatex, use a temp dir in the working directory. Otherwise we can have problems with things like epstopdf.pl, which pdflatex runs to convert eps files and which won't run on a file above the working directory in restricted mode. --- src/Text/Pandoc/PDF.hs | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs index bb575d13f..fce463d34 100644 --- a/src/Text/Pandoc/PDF.hs +++ b/src/Text/Pandoc/PDF.hs @@ -130,9 +130,11 @@ makePDF "pdfroff" pdfargs writer opts doc = do verbosity <- getVerbosity liftIO $ ms2pdf verbosity args source makePDF program pdfargs writer opts doc = do - let withTemp = if takeBaseName program == "context" - then withTempDirectory "." - else withTempDir + -- With context and latex, we create a temp directory within + -- the working directory, since pdflatex sometimes tries to + -- use tools like epstopdf.pl, which are restricted if run + -- on files outside the working directory. + let withTemp = withTempDirectory "." commonState <- getCommonState verbosity <- getVerbosity liftIO $ withTemp "tex2pdf." $ \tmpdir -> do -- cgit v1.2.3 From 229db80ac23ab0b5dba396d7748fcba0d05c4785 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 21 Apr 2018 12:28:30 -0700 Subject: makePDF: Don't try to convert eps files. pdflatex converts them itself, and JuicyPixels can't do it. See #2067. --- src/Text/Pandoc/PDF.hs | 2 ++ 1 file changed, 2 insertions(+) (limited to 'src') diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs index fce463d34..c73ab2dd9 100644 --- a/src/Text/Pandoc/PDF.hs +++ b/src/Text/Pandoc/PDF.hs @@ -175,6 +175,8 @@ convertImage tmpdir fname = Just "image/png" -> doNothing Just "image/jpeg" -> doNothing Just "application/pdf" -> doNothing + -- Note: eps is converted by pdflatex using epstopdf.pl + Just "application/eps" -> doNothing Just "image/svg+xml" -> E.catch (do (exit, _) <- pipeProcess Nothing "rsvg-convert" ["-f","pdf","-a","-o",pdfOut,fname] BL.empty -- cgit v1.2.3 From 7fbe473b2e3b3b2b94be810b6385475c056a304a Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 21 Apr 2018 13:06:57 -0700 Subject: Markdown reader/writer: spacing adjustments in tables. * Markdown writer now includes a blank line at the end of the row in a single-row multiline table, to prevent it from being interpreted as a simple table. Closes #4578. * Markdown reader does a better job computing the relative width of the last column in a multiline table, so we can round-trip tables without constantly shrinking the last column. --- src/Text/Pandoc/Readers/Markdown.hs | 11 +++++-- src/Text/Pandoc/Writers/Markdown.hs | 5 +++- test/command/3348.md | 2 +- test/command/4578.md | 14 +++++++++ test/tables-rstsubset.native | 12 ++++---- test/tables.asciidoc | 6 ++-- test/tables.context | 16 +++++----- test/tables.custom | 6 ++-- test/tables.docbook4 | 6 ++-- test/tables.docbook5 | 6 ++-- test/tables.haddock | 60 ++++++++++++++++++------------------- test/tables.html4 | 12 ++++---- test/tables.html5 | 12 ++++---- test/tables.icml | 6 ++-- test/tables.jats | 6 ++-- test/tables.latex | 18 +++++------ test/tables.man | 6 ++-- test/tables.mediawiki | 6 ++-- test/tables.ms | 6 ++-- test/tables.native | 6 ++-- test/tables.plain | 16 +++++----- test/tables.rst | 60 ++++++++++++++++++------------------- test/tables.rtf | 16 +++++----- test/tables.texinfo | 6 ++-- test/tables.textile | 6 ++-- 25 files changed, 174 insertions(+), 152 deletions(-) create mode 100644 test/command/4578.md (limited to 'src') diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 0d1a83bab..156b2b622 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -1341,11 +1341,16 @@ multilineTableHeader headless = try $ do newline let (lengths, lines') = unzip dashes let indices = scanl (+) (length initSp) lines' + -- compensate for the fact that intercolumn spaces are + -- not included in the last index: + let indices' = case reverse indices of + [] -> [] + (x:xs) -> reverse (x+1:xs) rawHeadsList <- if headless then fmap (map (:[]) . tail . - splitStringByIndices (init indices)) $ lookAhead anyLine + splitStringByIndices (init indices')) $ lookAhead anyLine else return $ transpose $ map - (tail . splitStringByIndices (init indices)) + (tail . splitStringByIndices (init indices')) rawContent let aligns = zipWith alignType rawHeadsList lengths let rawHeads = if headless @@ -1353,7 +1358,7 @@ multilineTableHeader headless = try $ do else map (unlines . map trim) rawHeadsList heads <- fmap sequence $ mapM ((parseFromString' (mconcat <$> many plain)).trim) rawHeads - return (heads, aligns, indices) + return (heads, aligns, indices') -- Parse a grid table: starts with row of '-' on top, then header -- (which may be grid), then the rows, diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 3bfa8a012..075858e5e 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -732,7 +732,10 @@ pandocTable opts multiline headless aligns widths rawHeaders rawRows = do then empty else border <> cr <> head' let body = if multiline - then vsep rows' + then vsep rows' $$ + if length rows' < 2 + then blankline -- #4578 + else empty else vcat rows' let bottom = if headless then underline diff --git a/test/command/3348.md b/test/command/3348.md index 1457373c8..6e0c07033 100644 --- a/test/command/3348.md +++ b/test/command/3348.md @@ -7,7 +7,7 @@ line of text ----- ------------------------------------------------ ^D -[Table [] [AlignRight,AlignLeft] [8.333333333333333e-2,0.6666666666666666] +[Table [] [AlignRight,AlignLeft] [8.333333333333333e-2,0.6805555555555556] [[] ,[]] [[[Plain [Str "foo"]] diff --git a/test/command/4578.md b/test/command/4578.md new file mode 100644 index 000000000..8f12d0bf2 --- /dev/null +++ b/test/command/4578.md @@ -0,0 +1,14 @@ +``` +% pandoc -t markdown + ------ ------- --------------- --------------------- + One row 12.0 Example of a row that + spans multiple lines. + + ------ ------- --------------- --------------------- +^D + ------ ------- --------------- --------------------- + One row 12.0 Example of a row that + spans multiple lines. + + ------ ------- --------------- --------------------- +``` diff --git a/test/tables-rstsubset.native b/test/tables-rstsubset.native index 8b7ccdf76..5ea520d7c 100644 --- a/test/tables-rstsubset.native +++ b/test/tables-rstsubset.native @@ -53,7 +53,7 @@ ,[Plain [Str "1"]] ,[Plain [Str "1"]]]] ,Para [Str "Multiline",Space,Str "table",Space,Str "with",Space,Str "caption:"] -,Table [Str "Here\8217s",Space,Str "the",Space,Str "caption.",Space,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.1375,0.125,0.15,0.325] +,Table [Str "Here\8217s",Space,Str "the",Space,Str "caption.",Space,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.1375,0.125,0.15,0.3375] [[Plain [Str "Centered",SoftBreak,Str "Header"]] ,[Plain [Str "Left",SoftBreak,Str "Aligned"]] ,[Plain [Str "Right",SoftBreak,Str "Aligned"]] @@ -65,9 +65,9 @@ ,[[Plain [Str "Second"]] ,[Plain [Str "row"]] ,[Plain [Str "5.0"]] - ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",SoftBreak,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",SoftBreak,Str "between",Space,Str "rows."]]]] + ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]] ,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "caption:"] -,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.1375,0.125,0.15,0.325] +,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.1375,0.125,0.15,0.3375] [[Plain [Str "Centered",SoftBreak,Str "Header"]] ,[Plain [Str "Left",SoftBreak,Str "Aligned"]] ,[Plain [Str "Right",SoftBreak,Str "Aligned"]] @@ -79,7 +79,7 @@ ,[[Plain [Str "Second"]] ,[Plain [Str "row"]] ,[Plain [Str "5.0"]] - ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",SoftBreak,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",SoftBreak,Str "between",Space,Str "rows."]]]] + ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]] ,Para [Str "Table",Space,Str "without",Space,Str "column",Space,Str "headers:"] ,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [7.5e-2,7.5e-2,7.5e-2,7.5e-2] [[] @@ -99,7 +99,7 @@ ,[Plain [Str "1"]] ,[Plain [Str "1"]]]] ,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "column",Space,Str "headers:"] -,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.1375,0.125,0.15,0.325] +,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.1375,0.125,0.15,0.3375] [[] ,[] ,[] @@ -111,4 +111,4 @@ ,[[Plain [Str "Second"]] ,[Plain [Str "row"]] ,[Plain [Str "5.0"]] - ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",SoftBreak,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",SoftBreak,Str "between",Space,Str "rows."]]]]] + ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]]] diff --git a/test/tables.asciidoc b/test/tables.asciidoc index 91490a27a..75632157e 100644 --- a/test/tables.asciidoc +++ b/test/tables.asciidoc @@ -33,7 +33,7 @@ Simple table indented two spaces: Multiline table with caption: .Here’s the caption. It may span multiple lines. -[width="78%",cols="^21%,<17%,>20%,<42%",options="header",] +[width="80%",cols="^20%,<17%,>20%,<43%",options="header",] |======================================================================= |Centered Header |Left Aligned |Right Aligned |Default aligned |First |row |12.0 |Example of a row that spans multiple lines. @@ -42,7 +42,7 @@ Multiline table with caption: Multiline table without caption: -[width="78%",cols="^21%,<17%,>20%,<42%",options="header",] +[width="80%",cols="^20%,<17%,>20%,<43%",options="header",] |======================================================================= |Centered Header |Left Aligned |Right Aligned |Default aligned |First |row |12.0 |Example of a row that spans multiple lines. @@ -60,7 +60,7 @@ Table without column headers: Multiline table without column headers: -[width="78%",cols="^21%,<17%,>20%,42%",] +[width="80%",cols="^20%,<17%,>20%,43%",] |======================================================================= |First |row |12.0 |Example of a row that spans multiple lines. |Second |row |5.0 |Here’s another one. Note the blank line between rows. diff --git a/test/tables.context b/test/tables.context index 11dffc065..556d2c216 100644 --- a/test/tables.context +++ b/test/tables.context @@ -118,7 +118,7 @@ Multiline table with caption: \startxcell[align=middle,width={0.15\textwidth}] Centered Header \stopxcell \startxcell[align=right,width={0.14\textwidth}] Left Aligned \stopxcell \startxcell[align=left,width={0.16\textwidth}] Right Aligned \stopxcell -\startxcell[align=right,width={0.34\textwidth}] Default aligned \stopxcell +\startxcell[align=right,width={0.35\textwidth}] Default aligned \stopxcell \stopxrow \stopxtablehead \startxtablebody[body] @@ -126,7 +126,7 @@ Multiline table with caption: \startxcell[align=middle,width={0.15\textwidth}] First \stopxcell \startxcell[align=right,width={0.14\textwidth}] row \stopxcell \startxcell[align=left,width={0.16\textwidth}] 12.0 \stopxcell -\startxcell[align=right,width={0.34\textwidth}] Example of a row that spans +\startxcell[align=right,width={0.35\textwidth}] Example of a row that spans multiple lines. \stopxcell \stopxrow \stopxtablebody @@ -135,7 +135,7 @@ multiple lines. \stopxcell \startxcell[align=middle,width={0.15\textwidth}] Second \stopxcell \startxcell[align=right,width={0.14\textwidth}] row \stopxcell \startxcell[align=left,width={0.16\textwidth}] 5.0 \stopxcell -\startxcell[align=right,width={0.34\textwidth}] Here's another one. Note the +\startxcell[align=right,width={0.35\textwidth}] Here's another one. Note the blank line between rows. \stopxcell \stopxrow \stopxtablefoot @@ -151,7 +151,7 @@ Multiline table without caption: \startxcell[align=middle,width={0.15\textwidth}] Centered Header \stopxcell \startxcell[align=right,width={0.14\textwidth}] Left Aligned \stopxcell \startxcell[align=left,width={0.16\textwidth}] Right Aligned \stopxcell -\startxcell[align=right,width={0.34\textwidth}] Default aligned \stopxcell +\startxcell[align=right,width={0.35\textwidth}] Default aligned \stopxcell \stopxrow \stopxtablehead \startxtablebody[body] @@ -159,7 +159,7 @@ Multiline table without caption: \startxcell[align=middle,width={0.15\textwidth}] First \stopxcell \startxcell[align=right,width={0.14\textwidth}] row \stopxcell \startxcell[align=left,width={0.16\textwidth}] 12.0 \stopxcell -\startxcell[align=right,width={0.34\textwidth}] Example of a row that spans +\startxcell[align=right,width={0.35\textwidth}] Example of a row that spans multiple lines. \stopxcell \stopxrow \stopxtablebody @@ -168,7 +168,7 @@ multiple lines. \stopxcell \startxcell[align=middle,width={0.15\textwidth}] Second \stopxcell \startxcell[align=right,width={0.14\textwidth}] row \stopxcell \startxcell[align=left,width={0.16\textwidth}] 5.0 \stopxcell -\startxcell[align=right,width={0.34\textwidth}] Here's another one. Note the +\startxcell[align=right,width={0.35\textwidth}] Here's another one. Note the blank line between rows. \stopxcell \stopxrow \stopxtablefoot @@ -213,7 +213,7 @@ Multiline table without column headers: \startxcell[align=middle,width={0.15\textwidth}] First \stopxcell \startxcell[align=right,width={0.14\textwidth}] row \stopxcell \startxcell[align=left,width={0.16\textwidth}] 12.0 \stopxcell -\startxcell[width={0.34\textwidth}] Example of a row that spans multiple +\startxcell[width={0.35\textwidth}] Example of a row that spans multiple lines. \stopxcell \stopxrow \stopxtablebody @@ -222,7 +222,7 @@ lines. \stopxcell \startxcell[align=middle,width={0.15\textwidth}] Second \stopxcell \startxcell[align=right,width={0.14\textwidth}] row \stopxcell \startxcell[align=left,width={0.16\textwidth}] 5.0 \stopxcell -\startxcell[width={0.34\textwidth}] Here's another one. Note the blank line +\startxcell[width={0.35\textwidth}] Here's another one. Note the blank line between rows. \stopxcell \stopxrow \stopxtablefoot diff --git a/test/tables.custom b/test/tables.custom index 410b68d3f..b78b3a4e9 100644 --- a/test/tables.custom +++ b/test/tables.custom @@ -95,7 +95,7 @@ It may span multiple lines. - + Centered Header @@ -127,7 +127,7 @@ the blank line between rows. - + Centered Header @@ -182,7 +182,7 @@ the blank line between rows. - + First row diff --git a/test/tables.docbook4 b/test/tables.docbook4 index f86b1c390..a661805e5 100644 --- a/test/tables.docbook4 +++ b/test/tables.docbook4 @@ -228,7 +228,7 @@ - + @@ -285,7 +285,7 @@ - + @@ -397,7 +397,7 @@ - + diff --git a/test/tables.docbook5 b/test/tables.docbook5 index f86b1c390..a661805e5 100644 --- a/test/tables.docbook5 +++ b/test/tables.docbook5 @@ -228,7 +228,7 @@ - + @@ -285,7 +285,7 @@ - + @@ -397,7 +397,7 @@ - + diff --git a/test/tables.haddock b/test/tables.haddock index 678c5c15a..dcfc0f7ad 100644 --- a/test/tables.haddock +++ b/test/tables.haddock @@ -40,33 +40,33 @@ Simple table indented two spaces: Multiline table with caption: -> +----------+---------+-----------+-------------------------+ -> | Centered | Left | Right | Default aligned | -> | Header | Aligned | Aligned | | -> +==========+=========+===========+=========================+ -> | First | row | 12.0 | Example of a row that | -> | | | | spans multiple lines. | -> +----------+---------+-----------+-------------------------+ -> | Second | row | 5.0 | Here’s another one. | -> | | | | Note the blank line | -> | | | | between rows. | -> +----------+---------+-----------+-------------------------+ +> +----------+---------+-----------+--------------------------+ +> | Centered | Left | Right | Default aligned | +> | Header | Aligned | Aligned | | +> +==========+=========+===========+==========================+ +> | First | row | 12.0 | Example of a row that | +> | | | | spans multiple lines. | +> +----------+---------+-----------+--------------------------+ +> | Second | row | 5.0 | Here’s another one. Note | +> | | | | the blank line between | +> | | | | rows. | +> +----------+---------+-----------+--------------------------+ > > Here’s the caption. It may span multiple lines. Multiline table without caption: -> +----------+---------+-----------+-------------------------+ -> | Centered | Left | Right | Default aligned | -> | Header | Aligned | Aligned | | -> +==========+=========+===========+=========================+ -> | First | row | 12.0 | Example of a row that | -> | | | | spans multiple lines. | -> +----------+---------+-----------+-------------------------+ -> | Second | row | 5.0 | Here’s another one. | -> | | | | Note the blank line | -> | | | | between rows. | -> +----------+---------+-----------+-------------------------+ +> +----------+---------+-----------+--------------------------+ +> | Centered | Left | Right | Default aligned | +> | Header | Aligned | Aligned | | +> +==========+=========+===========+==========================+ +> | First | row | 12.0 | Example of a row that | +> | | | | spans multiple lines. | +> +----------+---------+-----------+--------------------------+ +> | Second | row | 5.0 | Here’s another one. Note | +> | | | | the blank line between | +> | | | | rows. | +> +----------+---------+-----------+--------------------------+ Table without column headers: @@ -80,11 +80,11 @@ Table without column headers: Multiline table without column headers: -> +----------+---------+-----------+-------------------------+ -> | First | row | 12.0 | Example of a row that | -> | | | | spans multiple lines. | -> +----------+---------+-----------+-------------------------+ -> | Second | row | 5.0 | Here’s another one. | -> | | | | Note the blank line | -> | | | | between rows. | -> +----------+---------+-----------+-------------------------+ +> +----------+---------+-----------+--------------------------+ +> | First | row | 12.0 | Example of a row that | +> | | | | spans multiple lines. | +> +----------+---------+-----------+--------------------------+ +> | Second | row | 5.0 | Here’s another one. Note | +> | | | | the blank line between | +> | | | | rows. | +> +----------+---------+-----------+--------------------------+ diff --git a/test/tables.html4 b/test/tables.html4 index 5bb7a7de2..0f699133b 100644 --- a/test/tables.html4 +++ b/test/tables.html4 @@ -94,13 +94,13 @@

Multiline table with caption:

- +
-+ @@ -126,12 +126,12 @@
Here’s the caption. It may span multiple lines.

Multiline table without caption:

- +
-+ @@ -180,12 +180,12 @@

Multiline table without column headers:

- +
-+ diff --git a/test/tables.html5 b/test/tables.html5 index 17a82110f..533d2fd25 100644 --- a/test/tables.html5 +++ b/test/tables.html5 @@ -94,13 +94,13 @@

Multiline table with caption:

- +
-+ @@ -126,12 +126,12 @@
Here’s the caption. It may span multiple lines.

Multiline table without caption:

- +
-+ @@ -180,12 +180,12 @@

Multiline table without column headers:

- +
-+ diff --git a/test/tables.icml b/test/tables.icml index 0280cafed..10945ef46 100644 --- a/test/tables.icml +++ b/test/tables.icml @@ -395,7 +395,7 @@ - + @@ -497,7 +497,7 @@ - + @@ -695,7 +695,7 @@ - + diff --git a/test/tables.jats b/test/tables.jats index 50e8498f4..70f71e384 100644 --- a/test/tables.jats +++ b/test/tables.jats @@ -122,7 +122,7 @@ - + @@ -152,7 +152,7 @@ - + @@ -208,7 +208,7 @@ - + diff --git a/test/tables.latex b/test/tables.latex index 759b35dfa..4616448a9 100644 --- a/test/tables.latex +++ b/test/tables.latex @@ -58,7 +58,7 @@ Centered Header\strut Left Aligned\strut \end{minipage} & \begin{minipage}[b]{0.14\columnwidth}\raggedleft Right Aligned\strut -\end{minipage} & \begin{minipage}[b]{0.30\columnwidth}\raggedright +\end{minipage} & \begin{minipage}[b]{0.31\columnwidth}\raggedright Default aligned\strut \end{minipage}\tabularnewline \midrule @@ -70,7 +70,7 @@ Centered Header\strut Left Aligned\strut \end{minipage} & \begin{minipage}[b]{0.14\columnwidth}\raggedleft Right Aligned\strut -\end{minipage} & \begin{minipage}[b]{0.30\columnwidth}\raggedright +\end{minipage} & \begin{minipage}[b]{0.31\columnwidth}\raggedright Default aligned\strut \end{minipage}\tabularnewline \midrule @@ -81,7 +81,7 @@ First\strut row\strut \end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft 12.0\strut -\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright +\end{minipage} & \begin{minipage}[t]{0.31\columnwidth}\raggedright Example of a row that spans multiple lines.\strut \end{minipage}\tabularnewline \begin{minipage}[t]{0.13\columnwidth}\centering @@ -90,7 +90,7 @@ Second\strut row\strut \end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft 5.0\strut -\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright +\end{minipage} & \begin{minipage}[t]{0.31\columnwidth}\raggedright Here's another one. Note the blank line between rows.\strut \end{minipage}\tabularnewline \bottomrule @@ -106,7 +106,7 @@ Centered Header\strut Left Aligned\strut \end{minipage} & \begin{minipage}[b]{0.14\columnwidth}\raggedleft Right Aligned\strut -\end{minipage} & \begin{minipage}[b]{0.30\columnwidth}\raggedright +\end{minipage} & \begin{minipage}[b]{0.31\columnwidth}\raggedright Default aligned\strut \end{minipage}\tabularnewline \midrule @@ -117,7 +117,7 @@ First\strut row\strut \end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft 12.0\strut -\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright +\end{minipage} & \begin{minipage}[t]{0.31\columnwidth}\raggedright Example of a row that spans multiple lines.\strut \end{minipage}\tabularnewline \begin{minipage}[t]{0.13\columnwidth}\centering @@ -126,7 +126,7 @@ Second\strut row\strut \end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft 5.0\strut -\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright +\end{minipage} & \begin{minipage}[t]{0.31\columnwidth}\raggedright Here's another one. Note the blank line between rows.\strut \end{minipage}\tabularnewline \bottomrule @@ -154,7 +154,7 @@ First\strut row\strut \end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft 12.0\strut -\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright +\end{minipage} & \begin{minipage}[t]{0.31\columnwidth}\raggedright Example of a row that spans multiple lines.\strut \end{minipage}\tabularnewline \begin{minipage}[t]{0.13\columnwidth}\centering @@ -163,7 +163,7 @@ Second\strut row\strut \end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft 5.0\strut -\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright +\end{minipage} & \begin{minipage}[t]{0.31\columnwidth}\raggedright Here's another one. Note the blank line between rows.\strut \end{minipage}\tabularnewline \bottomrule diff --git a/test/tables.man b/test/tables.man index dd6a3cce9..8c9385b4f 100644 --- a/test/tables.man +++ b/test/tables.man @@ -138,7 +138,7 @@ Multiline table with caption: Here's the caption. It may span multiple lines. .TS tab(@); -cw(10.5n) lw(9.6n) rw(11.4n) lw(23.6n). +cw(10.5n) lw(9.6n) rw(11.4n) lw(24.5n). T{ Centered Header T}@T{ @@ -174,7 +174,7 @@ Multiline table without caption: .PP .TS tab(@); -cw(10.5n) lw(9.6n) rw(11.4n) lw(23.6n). +cw(10.5n) lw(9.6n) rw(11.4n) lw(24.5n). T{ Centered Header T}@T{ @@ -244,7 +244,7 @@ Multiline table without column headers: .PP .TS tab(@); -cw(10.5n) lw(9.6n) rw(11.4n) lw(23.6n). +cw(10.5n) lw(9.6n) rw(11.4n) lw(24.5n). T{ First T}@T{ diff --git a/test/tables.mediawiki b/test/tables.mediawiki index ce7c17887..5402b286b 100644 --- a/test/tables.mediawiki +++ b/test/tables.mediawiki @@ -79,7 +79,7 @@ Multiline table with caption: !align="center" width="15%"| Centered Header !width="13%"| Left Aligned !align="right" width="16%"| Right Aligned -!width="33%"| Default aligned +!width="35%"| Default aligned |- |align="center"| First | row @@ -98,7 +98,7 @@ Multiline table without caption: !align="center" width="15%"| Centered Header !width="13%"| Left Aligned !align="right" width="16%"| Right Aligned -!width="33%"| Default aligned +!width="35%"| Default aligned |- |align="center"| First | row @@ -136,7 +136,7 @@ Multiline table without column headers: |align="center" width="15%"| First |width="13%"| row |align="right" width="16%"| 12.0 -|width="33%"| Example of a row that spans multiple lines. +|width="35%"| Example of a row that spans multiple lines. |- |align="center"| Second | row diff --git a/test/tables.ms b/test/tables.ms index 1ef6b52f4..6d9138c64 100644 --- a/test/tables.ms +++ b/test/tables.ms @@ -138,7 +138,7 @@ Multiline table with caption: Here’s the caption. It may span multiple lines. .TS delim(@@) tab( ); -cw(10.5n) lw(9.6n) rw(11.4n) lw(23.6n). +cw(10.5n) lw(9.6n) rw(11.4n) lw(24.5n). T{ Centered Header T} T{ @@ -174,7 +174,7 @@ Multiline table without caption: .PP .TS delim(@@) tab( ); -cw(10.5n) lw(9.6n) rw(11.4n) lw(23.6n). +cw(10.5n) lw(9.6n) rw(11.4n) lw(24.5n). T{ Centered Header T} T{ @@ -244,7 +244,7 @@ Multiline table without column headers: .PP .TS delim(@@) tab( ); -cw(10.5n) lw(9.6n) rw(11.4n) lw(23.6n). +cw(10.5n) lw(9.6n) rw(11.4n) lw(24.5n). T{ First T} T{ diff --git a/test/tables.native b/test/tables.native index a60f9b586..62ed56bb4 100644 --- a/test/tables.native +++ b/test/tables.native @@ -53,7 +53,7 @@ ,[Plain [Str "1"]] ,[Plain [Str "1"]]]] ,Para [Str "Multiline",Space,Str "table",Space,Str "with",Space,Str "caption:"] -,Table [Str "Here\8217s",Space,Str "the",Space,Str "caption.",SoftBreak,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.15,0.1375,0.1625,0.3375] +,Table [Str "Here\8217s",Space,Str "the",Space,Str "caption.",SoftBreak,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.15,0.1375,0.1625,0.35] [[Plain [Str "Centered",SoftBreak,Str "Header"]] ,[Plain [Str "Left",SoftBreak,Str "Aligned"]] ,[Plain [Str "Right",SoftBreak,Str "Aligned"]] @@ -67,7 +67,7 @@ ,[Plain [Str "5.0"]] ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]] ,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "caption:"] -,Table [] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.15,0.1375,0.1625,0.3375] +,Table [] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.15,0.1375,0.1625,0.35] [[Plain [Str "Centered",SoftBreak,Str "Header"]] ,[Plain [Str "Left",SoftBreak,Str "Aligned"]] ,[Plain [Str "Right",SoftBreak,Str "Aligned"]] @@ -99,7 +99,7 @@ ,[Plain [Str "1"]] ,[Plain [Str "1"]]]] ,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "column",Space,Str "headers:"] -,Table [] [AlignCenter,AlignLeft,AlignRight,AlignDefault] [0.15,0.1375,0.1625,0.3375] +,Table [] [AlignCenter,AlignLeft,AlignRight,AlignDefault] [0.15,0.1375,0.1625,0.35] [[] ,[] ,[] diff --git a/test/tables.plain b/test/tables.plain index 7013d0caa..e46317a6f 100644 --- a/test/tables.plain +++ b/test/tables.plain @@ -28,33 +28,33 @@ Simple table indented two spaces: Multiline table with caption: - ------------------------------------------------------------- + -------------------------------------------------------------- Centered Left Right Default aligned Header Aligned Aligned - ----------- ---------- ------------ ------------------------- + ----------- ---------- ------------ -------------------------- First row 12.0 Example of a row that spans multiple lines. Second row 5.0 Here’s another one. Note the blank line between rows. - ------------------------------------------------------------- + -------------------------------------------------------------- : Here’s the caption. It may span multiple lines. Multiline table without caption: - ------------------------------------------------------------- + -------------------------------------------------------------- Centered Left Right Default aligned Header Aligned Aligned - ----------- ---------- ------------ ------------------------- + ----------- ---------- ------------ -------------------------- First row 12.0 Example of a row that spans multiple lines. Second row 5.0 Here’s another one. Note the blank line between rows. - ------------------------------------------------------------- + -------------------------------------------------------------- Table without column headers: @@ -66,11 +66,11 @@ Table without column headers: Multiline table without column headers: - ----------- ---------- ------------ ------------------------- + ----------- ---------- ------------ -------------------------- First row 12.0 Example of a row that spans multiple lines. Second row 5.0 Here’s another one. Note the blank line between rows. - ----------- ---------- ------------ ------------------------- + ----------- ---------- ------------ -------------------------- diff --git a/test/tables.rst b/test/tables.rst index e76c505aa..4559883cd 100644 --- a/test/tables.rst +++ b/test/tables.rst @@ -42,31 +42,31 @@ Multiline table with caption: .. table:: Here’s the caption. It may span multiple lines. - +----------+---------+-----------+-------------------------+ - | Centered | Left | Right | Default aligned | - | Header | Aligned | Aligned | | - +==========+=========+===========+=========================+ - | First | row | 12.0 | Example of a row that | - | | | | spans multiple lines. | - +----------+---------+-----------+-------------------------+ - | Second | row | 5.0 | Here’s another one. | - | | | | Note the blank line | - | | | | between rows. | - +----------+---------+-----------+-------------------------+ + +----------+---------+-----------+--------------------------+ + | Centered | Left | Right | Default aligned | + | Header | Aligned | Aligned | | + +==========+=========+===========+==========================+ + | First | row | 12.0 | Example of a row that | + | | | | spans multiple lines. | + +----------+---------+-----------+--------------------------+ + | Second | row | 5.0 | Here’s another one. Note | + | | | | the blank line between | + | | | | rows. | + +----------+---------+-----------+--------------------------+ Multiline table without caption: -+----------+---------+-----------+-------------------------+ -| Centered | Left | Right | Default aligned | -| Header | Aligned | Aligned | | -+==========+=========+===========+=========================+ -| First | row | 12.0 | Example of a row that | -| | | | spans multiple lines. | -+----------+---------+-----------+-------------------------+ -| Second | row | 5.0 | Here’s another one. | -| | | | Note the blank line | -| | | | between rows. | -+----------+---------+-----------+-------------------------+ ++----------+---------+-----------+--------------------------+ +| Centered | Left | Right | Default aligned | +| Header | Aligned | Aligned | | ++==========+=========+===========+==========================+ +| First | row | 12.0 | Example of a row that | +| | | | spans multiple lines. | ++----------+---------+-----------+--------------------------+ +| Second | row | 5.0 | Here’s another one. Note | +| | | | the blank line between | +| | | | rows. | ++----------+---------+-----------+--------------------------+ Table without column headers: @@ -80,11 +80,11 @@ Table without column headers: Multiline table without column headers: -+----------+---------+-----------+-------------------------+ -| First | row | 12.0 | Example of a row that | -| | | | spans multiple lines. | -+----------+---------+-----------+-------------------------+ -| Second | row | 5.0 | Here’s another one. | -| | | | Note the blank line | -| | | | between rows. | -+----------+---------+-----------+-------------------------+ ++----------+---------+-----------+--------------------------+ +| First | row | 12.0 | Example of a row that | +| | | | spans multiple lines. | ++----------+---------+-----------+--------------------------+ +| Second | row | 5.0 | Here’s another one. Note | +| | | | the blank line between | +| | | | rows. | ++----------+---------+-----------+--------------------------+ diff --git a/test/tables.rtf b/test/tables.rtf index 57030b114..97ea46bad 100644 --- a/test/tables.rtf +++ b/test/tables.rtf @@ -187,7 +187,7 @@ {\pard \ql \f0 \sa180 \li0 \fi0 Multiline table with caption:\par} { \trowd \trgaph120 -\clbrdrb\brdrs\cellx1296\clbrdrb\brdrs\cellx2484\clbrdrb\brdrs\cellx3888\clbrdrb\brdrs\cellx6804 +\clbrdrb\brdrs\cellx1296\clbrdrb\brdrs\cellx2484\clbrdrb\brdrs\cellx3888\clbrdrb\brdrs\cellx6912 \trkeep\intbl { {{\pard\intbl \qc \f0 \sa0 \li0 \fi0 Centered Header\par} @@ -202,7 +202,7 @@ \intbl\row} { \trowd \trgaph120 -\cellx1296\cellx2484\cellx3888\cellx6804 +\cellx1296\cellx2484\cellx3888\cellx6912 \trkeep\intbl { {{\pard\intbl \qc \f0 \sa0 \li0 \fi0 First\par} @@ -217,7 +217,7 @@ \intbl\row} { \trowd \trgaph120 -\cellx1296\cellx2484\cellx3888\cellx6804 +\cellx1296\cellx2484\cellx3888\cellx6912 \trkeep\intbl { {{\pard\intbl \qc \f0 \sa0 \li0 \fi0 Second\par} @@ -234,7 +234,7 @@ {\pard \ql \f0 \sa180 \li0 \fi0 Multiline table without caption:\par} { \trowd \trgaph120 -\clbrdrb\brdrs\cellx1296\clbrdrb\brdrs\cellx2484\clbrdrb\brdrs\cellx3888\clbrdrb\brdrs\cellx6804 +\clbrdrb\brdrs\cellx1296\clbrdrb\brdrs\cellx2484\clbrdrb\brdrs\cellx3888\clbrdrb\brdrs\cellx6912 \trkeep\intbl { {{\pard\intbl \qc \f0 \sa0 \li0 \fi0 Centered Header\par} @@ -249,7 +249,7 @@ \intbl\row} { \trowd \trgaph120 -\cellx1296\cellx2484\cellx3888\cellx6804 +\cellx1296\cellx2484\cellx3888\cellx6912 \trkeep\intbl { {{\pard\intbl \qc \f0 \sa0 \li0 \fi0 First\par} @@ -264,7 +264,7 @@ \intbl\row} { \trowd \trgaph120 -\cellx1296\cellx2484\cellx3888\cellx6804 +\cellx1296\cellx2484\cellx3888\cellx6912 \trkeep\intbl { {{\pard\intbl \qc \f0 \sa0 \li0 \fi0 Second\par} @@ -328,7 +328,7 @@ {\pard \ql \f0 \sa180 \li0 \fi0 Multiline table without column headers:\par} { \trowd \trgaph120 -\cellx1296\cellx2484\cellx3888\cellx6804 +\cellx1296\cellx2484\cellx3888\cellx6912 \trkeep\intbl { {{\pard\intbl \qc \f0 \sa0 \li0 \fi0 First\par} @@ -343,7 +343,7 @@ \intbl\row} { \trowd \trgaph120 -\cellx1296\cellx2484\cellx3888\cellx6804 +\cellx1296\cellx2484\cellx3888\cellx6912 \trkeep\intbl { {{\pard\intbl \qc \f0 \sa0 \li0 \fi0 Second\par} diff --git a/test/tables.texinfo b/test/tables.texinfo index b82006f1a..4f09246af 100644 --- a/test/tables.texinfo +++ b/test/tables.texinfo @@ -83,7 +83,7 @@ Right Multiline table with caption: @float -@multitable @columnfractions 0.15 0.14 0.16 0.34 +@multitable @columnfractions 0.15 0.14 0.16 0.35 @headitem Centered Header @tab Left Aligned @@ -104,7 +104,7 @@ Second @end float Multiline table without caption: -@multitable @columnfractions 0.15 0.14 0.16 0.34 +@multitable @columnfractions 0.15 0.14 0.16 0.35 @headitem Centered Header @tab Left Aligned @@ -144,7 +144,7 @@ Table without column headers: Multiline table without column headers: -@multitable @columnfractions 0.15 0.14 0.16 0.34 +@multitable @columnfractions 0.15 0.14 0.16 0.35 @item First @tab row diff --git a/test/tables.textile b/test/tables.textile index 6c6b234e6..9c71ec383 100644 --- a/test/tables.textile +++ b/test/tables.textile @@ -80,7 +80,7 @@ Multiline table with caption: -+ @@ -111,7 +111,7 @@ Multiline table without caption: -+ @@ -148,7 +148,7 @@ Multiline table without column headers: -+ -- cgit v1.2.3 From dab3330a585a55721821a8526a56510011a1145e Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 22 Apr 2018 12:18:45 -0700 Subject: RST reader: allow < 3 spaces indent under directives. Closes #4579. --- src/Text/Pandoc/Readers/RST.hs | 10 +++++++--- test/command/4579.md | 16 ++++++++++++++++ 2 files changed, 23 insertions(+), 3 deletions(-) create mode 100644 test/command/4579.md (limited to 'src') diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index 566f9b959..1577908a3 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -651,11 +651,15 @@ directive' = do skipMany spaceChar top <- many $ satisfy (/='\n') <|> try (char '\n' <* - notFollowedBy' (rawFieldListItem 3) <* - count 3 (char ' ') <* + notFollowedBy' (rawFieldListItem 1) <* + many1 (char ' ') <* notFollowedBy blankline) newline - fields <- many $ rawFieldListItem 3 + fields <- do + fieldIndent <- length <$> lookAhead (many (char ' ')) + if fieldIndent == 0 + then return [] + else many $ rawFieldListItem fieldIndent body <- option "" $ try $ blanklines >> indentedBlock optional blanklines let body' = body ++ "\n\n" diff --git a/test/command/4579.md b/test/command/4579.md new file mode 100644 index 000000000..80f0f58c2 --- /dev/null +++ b/test/command/4579.md @@ -0,0 +1,16 @@ +``` +% pandoc -f rst -t native +.. list-table:: + :header-rows: 1 + + * - Foo + - Bar + * - spam + - ham +^D +[Table [] [AlignDefault,AlignDefault] [0.0,0.0] + [[Plain [Str "Foo"]] + ,[Plain [Str "Bar"]]] + [[[Plain [Str "spam"]] + ,[Plain [Str "ham"]]]]] +``` -- cgit v1.2.3 From ad37fd8a03a14a0219f6069eb734a477b4e34722 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 25 Apr 2018 16:33:05 -0700 Subject: Added licensing headers for DocBook, EPUB, JATS, OPML readers. See #4592. --- COPYRIGHT | 12 ++++++++++++ src/Text/Pandoc/Readers/DocBook.hs | 29 +++++++++++++++++++++++++++++ src/Text/Pandoc/Readers/EPUB.hs | 30 +++++++++++++++++++++++++++++- src/Text/Pandoc/Readers/JATS.hs | 30 ++++++++++++++++++++++++++++++ src/Text/Pandoc/Readers/OPML.hs | 30 ++++++++++++++++++++++++++++++ 5 files changed, 130 insertions(+), 1 deletion(-) (limited to 'src') diff --git a/COPYRIGHT b/COPYRIGHT index 4d87adb02..0477bb450 100644 --- a/COPYRIGHT +++ b/COPYRIGHT @@ -119,6 +119,18 @@ Copyright (C) 2010-2018 Paul Rivier and John MacFarlane Released under the GNU General Public License version 2 or later. +---------------------------------------------------------------------- +src/Text/Pandoc/Readers/JATS.hs +Copyright (C) 2017-2018 Hamish Mackenzie + +Released under the GNU General Public License version 2 or later. + +---------------------------------------------------------------------- +src/Text/Pandoc/Readers/EPUB.hs +Copyright (C) 2014-2018 Matthew Pickering + +Released under the GNU General Public License version 2 or later. + ---------------------------------------------------------------------- src/Text/Pandoc/Readers/Org.hs src/Text/Pandoc/Readers/Org/* diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs index 5939f3888..809018697 100644 --- a/src/Text/Pandoc/Readers/DocBook.hs +++ b/src/Text/Pandoc/Readers/DocBook.hs @@ -1,4 +1,33 @@ {-# LANGUAGE NoImplicitPrelude #-} +{- +Copyright (C) 2006-2018 John MacFarlane + +This program is free software; you can redistribute it and/or modify +it under the terms of the GNU General Public License as published by +the Free Software Foundation; either version 2 of the License, or +(at your option) any later version. + +This program is distributed in the hope that it will be useful, +but WITHOUT ANY WARRANTY; without even the implied warranty of +MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +GNU General Public License for more details. + +You should have received a copy of the GNU General Public License +along with this program; if not, write to the Free Software +Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA +-} + +{- | + Module : Text.Pandoc.Readers.DocBook + Copyright : Copyright (C) 2006-2018 John MacFarlane + License : GNU GPL, version 2 or above + + Maintainer : John MacFarlane + Stability : alpha + Portability : portable + +Conversion of DocBook XML to 'Pandoc' document. +-} module Text.Pandoc.Readers.DocBook ( readDocBook ) where import Prelude import Control.Monad.State.Strict diff --git a/src/Text/Pandoc/Readers/EPUB.hs b/src/Text/Pandoc/Readers/EPUB.hs index 5c92c188b..c26447641 100644 --- a/src/Text/Pandoc/Readers/EPUB.hs +++ b/src/Text/Pandoc/Readers/EPUB.hs @@ -1,7 +1,35 @@ {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE ViewPatterns #-} - +{- +Copyright (C) 2014-2018 Matthew Pickering + +This program is free software; you can redistribute it and/or modify +it under the terms of the GNU General Public License as published by +the Free Software Foundation; either version 2 of the License, or +(at your option) any later version. + +This program is distributed in the hope that it will be useful, +but WITHOUT ANY WARRANTY; without even the implied warranty of +MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +GNU General Public License for more details. + +You should have received a copy of the GNU General Public License +along with this program; if not, write to the Free Software +Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA +-} + +{- | + Module : Text.Pandoc.Readers.EPUB + Copyright : Copyright (C) 2014-2018 Matthew Pickering + License : GNU GPL, version 2 or above + + Maintainer : John MacFarlane + Stability : alpha + Portability : portable + +Conversion of EPUB to 'Pandoc' document. +-} module Text.Pandoc.Readers.EPUB (readEPUB) diff --git a/src/Text/Pandoc/Readers/JATS.hs b/src/Text/Pandoc/Readers/JATS.hs index 29f23137c..59af76d23 100644 --- a/src/Text/Pandoc/Readers/JATS.hs +++ b/src/Text/Pandoc/Readers/JATS.hs @@ -1,5 +1,35 @@ {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE TupleSections #-} +{- +Copyright (C) 2017-2018 Hamish Mackenzie + +This program is free software; you can redistribute it and/or modify +it under the terms of the GNU General Public License as published by +the Free Software Foundation; either version 2 of the License, or +(at your option) any later version. + +This program is distributed in the hope that it will be useful, +but WITHOUT ANY WARRANTY; without even the implied warranty of +MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +GNU General Public License for more details. + +You should have received a copy of the GNU General Public License +along with this program; if not, write to the Free Software +Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA +-} + +{- | + Module : Text.Pandoc.Readers.JATS + Copyright : Copyright (C) 2017-2018 Hamish Mackenzie + License : GNU GPL, version 2 or above + + Maintainer : John MacFarlane + Stability : alpha + Portability : portable + +Conversion of JATS XML to 'Pandoc' document. +-} + module Text.Pandoc.Readers.JATS ( readJATS ) where import Prelude import Control.Monad.State.Strict diff --git a/src/Text/Pandoc/Readers/OPML.hs b/src/Text/Pandoc/Readers/OPML.hs index 3f4586295..1a489ab94 100644 --- a/src/Text/Pandoc/Readers/OPML.hs +++ b/src/Text/Pandoc/Readers/OPML.hs @@ -1,4 +1,34 @@ {-# LANGUAGE NoImplicitPrelude #-} +{- +Copyright (C) 2013-2018 John MacFarlane + +This program is free software; you can redistribute it and/or modify +it under the terms of the GNU General Public License as published by +the Free Software Foundation; either version 2 of the License, or +(at your option) any later version. + +This program is distributed in the hope that it will be useful, +but WITHOUT ANY WARRANTY; without even the implied warranty of +MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +GNU General Public License for more details. + +You should have received a copy of the GNU General Public License +along with this program; if not, write to the Free Software +Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA +-} + +{- | + Module : Text.Pandoc.Readers.OPML + Copyright : Copyright (C) 2013-2018 John MacFarlane + License : GNU GPL, version 2 or above + + Maintainer : John MacFarlane + Stability : alpha + Portability : portable + +Conversion of OPML to 'Pandoc' document. +-} + module Text.Pandoc.Readers.OPML ( readOPML ) where import Prelude import Control.Monad.State.Strict -- cgit v1.2.3 From 16f36eee43c9401612aa647eff4f041c4270e969 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 25 Apr 2018 17:05:37 -0700 Subject: Removed deprecated ancient HTML math methods. Removed `--latexmathml`, `--gladtex`, `--mimetex`, `--jsmath`, `-m`, `--asciimathml` options. Removed `JsMath`, `LaTeXMathML`, and `GladTeX` constructors from `Text.Pandoc.Options.HTMLMathMethod` [API change]. Removed unneeded data file LaTeXMathML.js and updated tests. Bumped version to 2.2. --- MANUAL.txt | 46 --------- data/LaTeXMathML.js | 198 -------------------------------------- pandoc.cabal | 4 +- src/Text/Pandoc/App.hs | 40 -------- src/Text/Pandoc/Options.hs | 3 - src/Text/Pandoc/Writers/HTML.hs | 25 ----- test/Tests/Old.hs | 2 +- test/s5-fancy.html | 204 +--------------------------------------- 8 files changed, 4 insertions(+), 518 deletions(-) delete mode 100644 data/LaTeXMathML.js (limited to 'src') diff --git a/MANUAL.txt b/MANUAL.txt index bc0db8868..938bacf20 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -1206,54 +1206,8 @@ of the following options. not specified, a link to the KaTeX CDN will be inserted. Note that this option does not imply `--katex`. -`-m` [*URL*], `--latexmathml`[`=`*URL*] - -: *Deprecated.* - Use the [LaTeXMathML] script to display embedded TeX math in HTML output. - TeX math will be displayed between `$` or `$$` characters and put in - `` tags with class `LaTeX`. The LaTeXMathML JavaScript will then - change it to MathML. Note that currently only Firefox and Safari - (and select e-book readers) natively support MathML. - To insert a link the `LaTeXMathML.js` script, provide a *URL*. - -`--jsmath`[`=`*URL*] - -: *Deprecated.* - Use [jsMath] (the predecessor of MathJax) to display embedded TeX - math in HTML output. TeX math will be put inside `` tags - (for inline math) or `
` tags (for display math) with class - `math` and rendered by the jsMath script. The *URL* should point to - the script (e.g. `jsMath/easy/load.js`); if provided, it will be linked - to in the header of standalone HTML documents. If a *URL* is not provided, - no link to the jsMath load script will be inserted; it is then - up to the author to provide such a link in the HTML template. - -`--gladtex` - -: *Deprecated.* - Enclose TeX math in `` tags in HTML output. The resulting HTML - can then be processed by [gladTeX] to produce images of the typeset - formulas and an HTML file with links to these images. - So, the procedure is: - - pandoc -s --gladtex input.md -o myfile.htex - gladtex -d myfile-images myfile.htex - # produces myfile.html and images in myfile-images - -`--mimetex`[`=`*URL*] - -: *Deprecated.* - Render TeX math using the [mimeTeX] CGI script, which generates an - image for each TeX formula. This should work in all browsers. If - *URL* is not specified, it is assumed that the script is at - `/cgi-bin/mimetex.cgi`. - [MathML]: http://www.w3.org/Math/ -[LaTeXMathML]: http://math.etsu.edu/LaTeXMathML/ -[jsMath]: http://www.math.union.edu/~dpvc/jsmath/ [MathJax]: https://www.mathjax.org -[gladTeX]: http://ans.hsh.no/home/mgg/gladtex/ -[mimeTeX]: http://www.forkosh.com/mimetex.html [KaTeX]: https://github.com/Khan/KaTeX Options for wrapper scripts diff --git a/data/LaTeXMathML.js b/data/LaTeXMathML.js deleted file mode 100644 index 4957624de..000000000 --- a/data/LaTeXMathML.js +++ /dev/null @@ -1,198 +0,0 @@ -/* -LaTeXMathML.js from http://math.etsu.edu/LaTeXMathML/ -Adapted by Jeff Knisely and Douglas Woodall from ASCIIMathML.js v. 1.4.7, -(c) 2005 Peter Jipsen http://www.chapman.edu/~jipsen. -Released under the GNU General Public License version 2 or later. -See the GNU General Public License (at http://www.gnu.org/copyleft/gpl.html) -for more details. -*/ -var checkForMathML=true;var notifyIfNoMathML=true;var alertIfNoMathML=false;var mathcolor="";var mathfontfamily="";var showasciiformulaonhover=true;var isIE=document.createElementNS==null;if(document.getElementById==null) -alert("This webpage requires a recent browser such as \nMozilla/Netscape 7+ or Internet Explorer 6+MathPlayer") -function AMcreateElementXHTML(t){if(isIE)return document.createElement(t);else return document.createElementNS("http://www.w3.org/1999/xhtml",t);} -function AMnoMathMLNote(){var nd=AMcreateElementXHTML("h3");nd.setAttribute("align","center") -nd.appendChild(AMcreateElementXHTML("p"));nd.appendChild(document.createTextNode("To view the "));var an=AMcreateElementXHTML("a");an.appendChild(document.createTextNode("LaTeXMathML"));an.setAttribute("href","http://www.maths.nott.ac.uk/personal/drw/lm.html");nd.appendChild(an);nd.appendChild(document.createTextNode(" notation use Internet Explorer 6+"));an=AMcreateElementXHTML("a");an.appendChild(document.createTextNode("MathPlayer"));an.setAttribute("href","http://www.dessci.com/en/products/mathplayer/download.htm");nd.appendChild(an);nd.appendChild(document.createTextNode(" or Netscape/Mozilla/Firefox"));nd.appendChild(AMcreateElementXHTML("p"));return nd;} -function AMisMathMLavailable(){if(navigator.appName.slice(0,8)=="Netscape") -if(navigator.appVersion.slice(0,1)>="5")return null;else return AMnoMathMLNote();else if(navigator.appName.slice(0,9)=="Microsoft") -try{var ActiveX=new ActiveXObject("MathPlayer.Factory.1");return null;}catch(e){return AMnoMathMLNote();} -else return AMnoMathMLNote();} -var AMcal=[0xEF35,0x212C,0xEF36,0xEF37,0x2130,0x2131,0xEF38,0x210B,0x2110,0xEF39,0xEF3A,0x2112,0x2133,0xEF3B,0xEF3C,0xEF3D,0xEF3E,0x211B,0xEF3F,0xEF40,0xEF41,0xEF42,0xEF43,0xEF44,0xEF45,0xEF46];var AMfrk=[0xEF5D,0xEF5E,0x212D,0xEF5F,0xEF60,0xEF61,0xEF62,0x210C,0x2111,0xEF63,0xEF64,0xEF65,0xEF66,0xEF67,0xEF68,0xEF69,0xEF6A,0x211C,0xEF6B,0xEF6C,0xEF6D,0xEF6E,0xEF6F,0xEF70,0xEF71,0x2128];var AMbbb=[0xEF8C,0xEF8D,0x2102,0xEF8E,0xEF8F,0xEF90,0xEF91,0x210D,0xEF92,0xEF93,0xEF94,0xEF95,0xEF96,0x2115,0xEF97,0x2119,0x211A,0x211D,0xEF98,0xEF99,0xEF9A,0xEF9B,0xEF9C,0xEF9D,0xEF9E,0x2124];var CONST=0,UNARY=1,BINARY=2,INFIX=3,LEFTBRACKET=4,RIGHTBRACKET=5,SPACE=6,UNDEROVER=7,DEFINITION=8,TEXT=9,BIG=10,LONG=11,STRETCHY=12,MATRIX=13;var AMsqrt={input:"\\sqrt",tag:"msqrt",output:"sqrt",ttype:UNARY},AMroot={input:"\\root",tag:"mroot",output:"root",ttype:BINARY},AMfrac={input:"\\frac",tag:"mfrac",output:"/",ttype:BINARY},AMover={input:"\\stackrel",tag:"mover",output:"stackrel",ttype:BINARY},AMatop={input:"\\atop",tag:"mfrac",output:"",ttype:INFIX},AMchoose={input:"\\choose",tag:"mfrac",output:"",ttype:INFIX},AMsub={input:"_",tag:"msub",output:"_",ttype:INFIX},AMsup={input:"^",tag:"msup",output:"^",ttype:INFIX},AMtext={input:"\\mathrm",tag:"mtext",output:"text",ttype:TEXT},AMmbox={input:"\\mbox",tag:"mtext",output:"mbox",ttype:TEXT};var AMsymbols=[{input:"\\alpha",tag:"mi",output:"\u03B1",ttype:CONST},{input:"\\beta",tag:"mi",output:"\u03B2",ttype:CONST},{input:"\\gamma",tag:"mi",output:"\u03B3",ttype:CONST},{input:"\\delta",tag:"mi",output:"\u03B4",ttype:CONST},{input:"\\epsilon",tag:"mi",output:"\u03B5",ttype:CONST},{input:"\\varepsilon",tag:"mi",output:"\u025B",ttype:CONST},{input:"\\zeta",tag:"mi",output:"\u03B6",ttype:CONST},{input:"\\eta",tag:"mi",output:"\u03B7",ttype:CONST},{input:"\\theta",tag:"mi",output:"\u03B8",ttype:CONST},{input:"\\vartheta",tag:"mi",output:"\u03D1",ttype:CONST},{input:"\\iota",tag:"mi",output:"\u03B9",ttype:CONST},{input:"\\kappa",tag:"mi",output:"\u03BA",ttype:CONST},{input:"\\lambda",tag:"mi",output:"\u03BB",ttype:CONST},{input:"\\mu",tag:"mi",output:"\u03BC",ttype:CONST},{input:"\\nu",tag:"mi",output:"\u03BD",ttype:CONST},{input:"\\xi",tag:"mi",output:"\u03BE",ttype:CONST},{input:"\\pi",tag:"mi",output:"\u03C0",ttype:CONST},{input:"\\varpi",tag:"mi",output:"\u03D6",ttype:CONST},{input:"\\rho",tag:"mi",output:"\u03C1",ttype:CONST},{input:"\\varrho",tag:"mi",output:"\u03F1",ttype:CONST},{input:"\\varsigma",tag:"mi",output:"\u03C2",ttype:CONST},{input:"\\sigma",tag:"mi",output:"\u03C3",ttype:CONST},{input:"\\tau",tag:"mi",output:"\u03C4",ttype:CONST},{input:"\\upsilon",tag:"mi",output:"\u03C5",ttype:CONST},{input:"\\phi",tag:"mi",output:"\u03C6",ttype:CONST},{input:"\\varphi",tag:"mi",output:"\u03D5",ttype:CONST},{input:"\\chi",tag:"mi",output:"\u03C7",ttype:CONST},{input:"\\psi",tag:"mi",output:"\u03C8",ttype:CONST},{input:"\\omega",tag:"mi",output:"\u03C9",ttype:CONST},{input:"\\Gamma",tag:"mo",output:"\u0393",ttype:CONST},{input:"\\Delta",tag:"mo",output:"\u0394",ttype:CONST},{input:"\\Theta",tag:"mo",output:"\u0398",ttype:CONST},{input:"\\Lambda",tag:"mo",output:"\u039B",ttype:CONST},{input:"\\Xi",tag:"mo",output:"\u039E",ttype:CONST},{input:"\\Pi",tag:"mo",output:"\u03A0",ttype:CONST},{input:"\\Sigma",tag:"mo",output:"\u03A3",ttype:CONST},{input:"\\Upsilon",tag:"mo",output:"\u03A5",ttype:CONST},{input:"\\Phi",tag:"mo",output:"\u03A6",ttype:CONST},{input:"\\Psi",tag:"mo",output:"\u03A8",ttype:CONST},{input:"\\Omega",tag:"mo",output:"\u03A9",ttype:CONST},{input:"\\frac12",tag:"mo",output:"\u00BD",ttype:CONST},{input:"\\frac14",tag:"mo",output:"\u00BC",ttype:CONST},{input:"\\frac34",tag:"mo",output:"\u00BE",ttype:CONST},{input:"\\frac13",tag:"mo",output:"\u2153",ttype:CONST},{input:"\\frac23",tag:"mo",output:"\u2154",ttype:CONST},{input:"\\frac15",tag:"mo",output:"\u2155",ttype:CONST},{input:"\\frac25",tag:"mo",output:"\u2156",ttype:CONST},{input:"\\frac35",tag:"mo",output:"\u2157",ttype:CONST},{input:"\\frac45",tag:"mo",output:"\u2158",ttype:CONST},{input:"\\frac16",tag:"mo",output:"\u2159",ttype:CONST},{input:"\\frac56",tag:"mo",output:"\u215A",ttype:CONST},{input:"\\frac18",tag:"mo",output:"\u215B",ttype:CONST},{input:"\\frac38",tag:"mo",output:"\u215C",ttype:CONST},{input:"\\frac58",tag:"mo",output:"\u215D",ttype:CONST},{input:"\\frac78",tag:"mo",output:"\u215E",ttype:CONST},{input:"\\pm",tag:"mo",output:"\u00B1",ttype:CONST},{input:"\\mp",tag:"mo",output:"\u2213",ttype:CONST},{input:"\\triangleleft",tag:"mo",output:"\u22B2",ttype:CONST},{input:"\\triangleright",tag:"mo",output:"\u22B3",ttype:CONST},{input:"\\cdot",tag:"mo",output:"\u22C5",ttype:CONST},{input:"\\star",tag:"mo",output:"\u22C6",ttype:CONST},{input:"\\ast",tag:"mo",output:"\u002A",ttype:CONST},{input:"\\times",tag:"mo",output:"\u00D7",ttype:CONST},{input:"\\div",tag:"mo",output:"\u00F7",ttype:CONST},{input:"\\circ",tag:"mo",output:"\u2218",ttype:CONST},{input:"\\bullet",tag:"mo",output:"\u2022",ttype:CONST},{input:"\\oplus",tag:"mo",output:"\u2295",ttype:CONST},{input:"\\ominus",tag:"mo",output:"\u2296",ttype:CONST},{input:"\\otimes",tag:"mo",output:"\u2297",ttype:CONST},{input:"\\bigcirc",tag:"mo",output:"\u25CB",ttype:CONST},{input:"\\oslash",tag:"mo",output:"\u2298",ttype:CONST},{input:"\\odot",tag:"mo",output:"\u2299",ttype:CONST},{input:"\\land",tag:"mo",output:"\u2227",ttype:CONST},{input:"\\wedge",tag:"mo",output:"\u2227",ttype:CONST},{input:"\\lor",tag:"mo",output:"\u2228",ttype:CONST},{input:"\\vee",tag:"mo",output:"\u2228",ttype:CONST},{input:"\\cap",tag:"mo",output:"\u2229",ttype:CONST},{input:"\\cup",tag:"mo",output:"\u222A",ttype:CONST},{input:"\\sqcap",tag:"mo",output:"\u2293",ttype:CONST},{input:"\\sqcup",tag:"mo",output:"\u2294",ttype:CONST},{input:"\\uplus",tag:"mo",output:"\u228E",ttype:CONST},{input:"\\amalg",tag:"mo",output:"\u2210",ttype:CONST},{input:"\\bigtriangleup",tag:"mo",output:"\u25B3",ttype:CONST},{input:"\\bigtriangledown",tag:"mo",output:"\u25BD",ttype:CONST},{input:"\\dag",tag:"mo",output:"\u2020",ttype:CONST},{input:"\\dagger",tag:"mo",output:"\u2020",ttype:CONST},{input:"\\ddag",tag:"mo",output:"\u2021",ttype:CONST},{input:"\\ddagger",tag:"mo",output:"\u2021",ttype:CONST},{input:"\\lhd",tag:"mo",output:"\u22B2",ttype:CONST},{input:"\\rhd",tag:"mo",output:"\u22B3",ttype:CONST},{input:"\\unlhd",tag:"mo",output:"\u22B4",ttype:CONST},{input:"\\unrhd",tag:"mo",output:"\u22B5",ttype:CONST},{input:"\\sum",tag:"mo",output:"\u2211",ttype:UNDEROVER},{input:"\\prod",tag:"mo",output:"\u220F",ttype:UNDEROVER},{input:"\\bigcap",tag:"mo",output:"\u22C2",ttype:UNDEROVER},{input:"\\bigcup",tag:"mo",output:"\u22C3",ttype:UNDEROVER},{input:"\\bigwedge",tag:"mo",output:"\u22C0",ttype:UNDEROVER},{input:"\\bigvee",tag:"mo",output:"\u22C1",ttype:UNDEROVER},{input:"\\bigsqcap",tag:"mo",output:"\u2A05",ttype:UNDEROVER},{input:"\\bigsqcup",tag:"mo",output:"\u2A06",ttype:UNDEROVER},{input:"\\coprod",tag:"mo",output:"\u2210",ttype:UNDEROVER},{input:"\\bigoplus",tag:"mo",output:"\u2A01",ttype:UNDEROVER},{input:"\\bigotimes",tag:"mo",output:"\u2A02",ttype:UNDEROVER},{input:"\\bigodot",tag:"mo",output:"\u2A00",ttype:UNDEROVER},{input:"\\biguplus",tag:"mo",output:"\u2A04",ttype:UNDEROVER},{input:"\\int",tag:"mo",output:"\u222B",ttype:CONST},{input:"\\oint",tag:"mo",output:"\u222E",ttype:CONST},{input:":=",tag:"mo",output:":=",ttype:CONST},{input:"\\lt",tag:"mo",output:"<",ttype:CONST},{input:"\\gt",tag:"mo",output:">",ttype:CONST},{input:"\\ne",tag:"mo",output:"\u2260",ttype:CONST},{input:"\\neq",tag:"mo",output:"\u2260",ttype:CONST},{input:"\\le",tag:"mo",output:"\u2264",ttype:CONST},{input:"\\leq",tag:"mo",output:"\u2264",ttype:CONST},{input:"\\leqslant",tag:"mo",output:"\u2264",ttype:CONST},{input:"\\ge",tag:"mo",output:"\u2265",ttype:CONST},{input:"\\geq",tag:"mo",output:"\u2265",ttype:CONST},{input:"\\geqslant",tag:"mo",output:"\u2265",ttype:CONST},{input:"\\equiv",tag:"mo",output:"\u2261",ttype:CONST},{input:"\\ll",tag:"mo",output:"\u226A",ttype:CONST},{input:"\\gg",tag:"mo",output:"\u226B",ttype:CONST},{input:"\\doteq",tag:"mo",output:"\u2250",ttype:CONST},{input:"\\prec",tag:"mo",output:"\u227A",ttype:CONST},{input:"\\succ",tag:"mo",output:"\u227B",ttype:CONST},{input:"\\preceq",tag:"mo",output:"\u227C",ttype:CONST},{input:"\\succeq",tag:"mo",output:"\u227D",ttype:CONST},{input:"\\subset",tag:"mo",output:"\u2282",ttype:CONST},{input:"\\supset",tag:"mo",output:"\u2283",ttype:CONST},{input:"\\subseteq",tag:"mo",output:"\u2286",ttype:CONST},{input:"\\supseteq",tag:"mo",output:"\u2287",ttype:CONST},{input:"\\sqsubset",tag:"mo",output:"\u228F",ttype:CONST},{input:"\\sqsupset",tag:"mo",output:"\u2290",ttype:CONST},{input:"\\sqsubseteq",tag:"mo",output:"\u2291",ttype:CONST},{input:"\\sqsupseteq",tag:"mo",output:"\u2292",ttype:CONST},{input:"\\sim",tag:"mo",output:"\u223C",ttype:CONST},{input:"\\simeq",tag:"mo",output:"\u2243",ttype:CONST},{input:"\\approx",tag:"mo",output:"\u2248",ttype:CONST},{input:"\\cong",tag:"mo",output:"\u2245",ttype:CONST},{input:"\\Join",tag:"mo",output:"\u22C8",ttype:CONST},{input:"\\bowtie",tag:"mo",output:"\u22C8",ttype:CONST},{input:"\\in",tag:"mo",output:"\u2208",ttype:CONST},{input:"\\ni",tag:"mo",output:"\u220B",ttype:CONST},{input:"\\owns",tag:"mo",output:"\u220B",ttype:CONST},{input:"\\propto",tag:"mo",output:"\u221D",ttype:CONST},{input:"\\vdash",tag:"mo",output:"\u22A2",ttype:CONST},{input:"\\dashv",tag:"mo",output:"\u22A3",ttype:CONST},{input:"\\models",tag:"mo",output:"\u22A8",ttype:CONST},{input:"\\perp",tag:"mo",output:"\u22A5",ttype:CONST},{input:"\\smile",tag:"mo",output:"\u2323",ttype:CONST},{input:"\\frown",tag:"mo",output:"\u2322",ttype:CONST},{input:"\\asymp",tag:"mo",output:"\u224D",ttype:CONST},{input:"\\notin",tag:"mo",output:"\u2209",ttype:CONST},{input:"\\begin{eqnarray}",output:"X",ttype:MATRIX,invisible:true},{input:"\\begin{array}",output:"X",ttype:MATRIX,invisible:true},{input:"\\\\",output:"}&{",ttype:DEFINITION},{input:"\\end{eqnarray}",output:"}}",ttype:DEFINITION},{input:"\\end{array}",output:"}}",ttype:DEFINITION},{input:"\\big",tag:"mo",output:"X",atval:"1.2",ieval:"2.2",ttype:BIG},{input:"\\Big",tag:"mo",output:"X",atval:"1.6",ieval:"2.6",ttype:BIG},{input:"\\bigg",tag:"mo",output:"X",atval:"2.2",ieval:"3.2",ttype:BIG},{input:"\\Bigg",tag:"mo",output:"X",atval:"2.9",ieval:"3.9",ttype:BIG},{input:"\\left",tag:"mo",output:"X",ttype:LEFTBRACKET},{input:"\\right",tag:"mo",output:"X",ttype:RIGHTBRACKET},{input:"{",output:"{",ttype:LEFTBRACKET,invisible:true},{input:"}",output:"}",ttype:RIGHTBRACKET,invisible:true},{input:"(",tag:"mo",output:"(",atval:"1",ttype:STRETCHY},{input:"[",tag:"mo",output:"[",atval:"1",ttype:STRETCHY},{input:"\\lbrack",tag:"mo",output:"[",atval:"1",ttype:STRETCHY},{input:"\\{",tag:"mo",output:"{",atval:"1",ttype:STRETCHY},{input:"\\lbrace",tag:"mo",output:"{",atval:"1",ttype:STRETCHY},{input:"\\langle",tag:"mo",output:"\u2329",atval:"1",ttype:STRETCHY},{input:"\\lfloor",tag:"mo",output:"\u230A",atval:"1",ttype:STRETCHY},{input:"\\lceil",tag:"mo",output:"\u2308",atval:"1",ttype:STRETCHY},{input:")",tag:"mo",output:")",rtag:"mi",atval:"1",ttype:STRETCHY},{input:"]",tag:"mo",output:"]",rtag:"mi",atval:"1",ttype:STRETCHY},{input:"\\rbrack",tag:"mo",output:"]",rtag:"mi",atval:"1",ttype:STRETCHY},{input:"\\}",tag:"mo",output:"}",rtag:"mi",atval:"1",ttype:STRETCHY},{input:"\\rbrace",tag:"mo",output:"}",rtag:"mi",atval:"1",ttype:STRETCHY},{input:"\\rangle",tag:"mo",output:"\u232A",rtag:"mi",atval:"1",ttype:STRETCHY},{input:"\\rfloor",tag:"mo",output:"\u230B",rtag:"mi",atval:"1",ttype:STRETCHY},{input:"\\rceil",tag:"mo",output:"\u2309",rtag:"mi",atval:"1",ttype:STRETCHY},{input:"|",tag:"mo",output:"\u2223",atval:"1",ttype:STRETCHY},{input:"\\|",tag:"mo",output:"\u2225",atval:"1",ttype:STRETCHY},{input:"\\vert",tag:"mo",output:"\u2223",atval:"1",ttype:STRETCHY},{input:"\\Vert",tag:"mo",output:"\u2225",atval:"1",ttype:STRETCHY},{input:"\\mid",tag:"mo",output:"\u2223",atval:"1",ttype:STRETCHY},{input:"\\parallel",tag:"mo",output:"\u2225",atval:"1",ttype:STRETCHY},{input:"/",tag:"mo",output:"/",atval:"1.01",ttype:STRETCHY},{input:"\\backslash",tag:"mo",output:"\u2216",atval:"1",ttype:STRETCHY},{input:"\\setminus",tag:"mo",output:"\\",ttype:CONST},{input:"\\!",tag:"mspace",atname:"width",atval:"-0.167em",ttype:SPACE},{input:"\\,",tag:"mspace",atname:"width",atval:"0.167em",ttype:SPACE},{input:"\\>",tag:"mspace",atname:"width",atval:"0.222em",ttype:SPACE},{input:"\\:",tag:"mspace",atname:"width",atval:"0.222em",ttype:SPACE},{input:"\\;",tag:"mspace",atname:"width",atval:"0.278em",ttype:SPACE},{input:"~",tag:"mspace",atname:"width",atval:"0.333em",ttype:SPACE},{input:"\\quad",tag:"mspace",atname:"width",atval:"1em",ttype:SPACE},{input:"\\qquad",tag:"mspace",atname:"width",atval:"2em",ttype:SPACE},{input:"\\prime",tag:"mo",output:"\u2032",ttype:CONST},{input:"'",tag:"mo",output:"\u02B9",ttype:CONST},{input:"''",tag:"mo",output:"\u02BA",ttype:CONST},{input:"'''",tag:"mo",output:"\u2034",ttype:CONST},{input:"''''",tag:"mo",output:"\u2057",ttype:CONST},{input:"\\ldots",tag:"mo",output:"\u2026",ttype:CONST},{input:"\\cdots",tag:"mo",output:"\u22EF",ttype:CONST},{input:"\\vdots",tag:"mo",output:"\u22EE",ttype:CONST},{input:"\\ddots",tag:"mo",output:"\u22F1",ttype:CONST},{input:"\\forall",tag:"mo",output:"\u2200",ttype:CONST},{input:"\\exists",tag:"mo",output:"\u2203",ttype:CONST},{input:"\\Re",tag:"mo",output:"\u211C",ttype:CONST},{input:"\\Im",tag:"mo",output:"\u2111",ttype:CONST},{input:"\\aleph",tag:"mo",output:"\u2135",ttype:CONST},{input:"\\hbar",tag:"mo",output:"\u210F",ttype:CONST},{input:"\\ell",tag:"mo",output:"\u2113",ttype:CONST},{input:"\\wp",tag:"mo",output:"\u2118",ttype:CONST},{input:"\\emptyset",tag:"mo",output:"\u2205",ttype:CONST},{input:"\\infty",tag:"mo",output:"\u221E",ttype:CONST},{input:"\\surd",tag:"mo",output:"\\sqrt{}",ttype:DEFINITION},{input:"\\partial",tag:"mo",output:"\u2202",ttype:CONST},{input:"\\nabla",tag:"mo",output:"\u2207",ttype:CONST},{input:"\\triangle",tag:"mo",output:"\u25B3",ttype:CONST},{input:"\\therefore",tag:"mo",output:"\u2234",ttype:CONST},{input:"\\angle",tag:"mo",output:"\u2220",ttype:CONST},{input:"\\diamond",tag:"mo",output:"\u22C4",ttype:CONST},{input:"\\Diamond",tag:"mo",output:"\u25C7",ttype:CONST},{input:"\\neg",tag:"mo",output:"\u00AC",ttype:CONST},{input:"\\lnot",tag:"mo",output:"\u00AC",ttype:CONST},{input:"\\bot",tag:"mo",output:"\u22A5",ttype:CONST},{input:"\\top",tag:"mo",output:"\u22A4",ttype:CONST},{input:"\\square",tag:"mo",output:"\u25AB",ttype:CONST},{input:"\\Box",tag:"mo",output:"\u25A1",ttype:CONST},{input:"\\wr",tag:"mo",output:"\u2240",ttype:CONST},{input:"\\arccos",tag:"mi",output:"arccos",ttype:UNARY,func:true},{input:"\\arcsin",tag:"mi",output:"arcsin",ttype:UNARY,func:true},{input:"\\arctan",tag:"mi",output:"arctan",ttype:UNARY,func:true},{input:"\\arg",tag:"mi",output:"arg",ttype:UNARY,func:true},{input:"\\cos",tag:"mi",output:"cos",ttype:UNARY,func:true},{input:"\\cosh",tag:"mi",output:"cosh",ttype:UNARY,func:true},{input:"\\cot",tag:"mi",output:"cot",ttype:UNARY,func:true},{input:"\\coth",tag:"mi",output:"coth",ttype:UNARY,func:true},{input:"\\csc",tag:"mi",output:"csc",ttype:UNARY,func:true},{input:"\\deg",tag:"mi",output:"deg",ttype:UNARY,func:true},{input:"\\det",tag:"mi",output:"det",ttype:UNARY,func:true},{input:"\\dim",tag:"mi",output:"dim",ttype:UNARY,func:true},{input:"\\exp",tag:"mi",output:"exp",ttype:UNARY,func:true},{input:"\\gcd",tag:"mi",output:"gcd",ttype:UNARY,func:true},{input:"\\hom",tag:"mi",output:"hom",ttype:UNARY,func:true},{input:"\\inf",tag:"mo",output:"inf",ttype:UNDEROVER},{input:"\\ker",tag:"mi",output:"ker",ttype:UNARY,func:true},{input:"\\lg",tag:"mi",output:"lg",ttype:UNARY,func:true},{input:"\\lim",tag:"mo",output:"lim",ttype:UNDEROVER},{input:"\\liminf",tag:"mo",output:"liminf",ttype:UNDEROVER},{input:"\\limsup",tag:"mo",output:"limsup",ttype:UNDEROVER},{input:"\\ln",tag:"mi",output:"ln",ttype:UNARY,func:true},{input:"\\log",tag:"mi",output:"log",ttype:UNARY,func:true},{input:"\\max",tag:"mo",output:"max",ttype:UNDEROVER},{input:"\\min",tag:"mo",output:"min",ttype:UNDEROVER},{input:"\\Pr",tag:"mi",output:"Pr",ttype:UNARY,func:true},{input:"\\sec",tag:"mi",output:"sec",ttype:UNARY,func:true},{input:"\\sin",tag:"mi",output:"sin",ttype:UNARY,func:true},{input:"\\sinh",tag:"mi",output:"sinh",ttype:UNARY,func:true},{input:"\\sup",tag:"mo",output:"sup",ttype:UNDEROVER},{input:"\\tan",tag:"mi",output:"tan",ttype:UNARY,func:true},{input:"\\tanh",tag:"mi",output:"tanh",ttype:UNARY,func:true},{input:"\\gets",tag:"mo",output:"\u2190",ttype:CONST},{input:"\\leftarrow",tag:"mo",output:"\u2190",ttype:CONST},{input:"\\to",tag:"mo",output:"\u2192",ttype:CONST},{input:"\\rightarrow",tag:"mo",output:"\u2192",ttype:CONST},{input:"\\leftrightarrow",tag:"mo",output:"\u2194",ttype:CONST},{input:"\\uparrow",tag:"mo",output:"\u2191",ttype:CONST},{input:"\\downarrow",tag:"mo",output:"\u2193",ttype:CONST},{input:"\\updownarrow",tag:"mo",output:"\u2195",ttype:CONST},{input:"\\Leftarrow",tag:"mo",output:"\u21D0",ttype:CONST},{input:"\\Rightarrow",tag:"mo",output:"\u21D2",ttype:CONST},{input:"\\Leftrightarrow",tag:"mo",output:"\u21D4",ttype:CONST},{input:"\\iff",tag:"mo",output:"~\\Longleftrightarrow~",ttype:DEFINITION},{input:"\\Uparrow",tag:"mo",output:"\u21D1",ttype:CONST},{input:"\\Downarrow",tag:"mo",output:"\u21D3",ttype:CONST},{input:"\\Updownarrow",tag:"mo",output:"\u21D5",ttype:CONST},{input:"\\mapsto",tag:"mo",output:"\u21A6",ttype:CONST},{input:"\\longleftarrow",tag:"mo",output:"\u2190",ttype:LONG},{input:"\\longrightarrow",tag:"mo",output:"\u2192",ttype:LONG},{input:"\\longleftrightarrow",tag:"mo",output:"\u2194",ttype:LONG},{input:"\\Longleftarrow",tag:"mo",output:"\u21D0",ttype:LONG},{input:"\\Longrightarrow",tag:"mo",output:"\u21D2",ttype:LONG},{input:"\\Longleftrightarrow",tag:"mo",output:"\u21D4",ttype:LONG},{input:"\\longmapsto",tag:"mo",output:"\u21A6",ttype:CONST},AMsqrt,AMroot,AMfrac,AMover,AMsub,AMsup,AMtext,AMmbox,AMatop,AMchoose,{input:"\\acute",tag:"mover",output:"\u00B4",ttype:UNARY,acc:true},{input:"\\grave",tag:"mover",output:"\u0060",ttype:UNARY,acc:true},{input:"\\breve",tag:"mover",output:"\u02D8",ttype:UNARY,acc:true},{input:"\\check",tag:"mover",output:"\u02C7",ttype:UNARY,acc:true},{input:"\\dot",tag:"mover",output:".",ttype:UNARY,acc:true},{input:"\\ddot",tag:"mover",output:"..",ttype:UNARY,acc:true},{input:"\\mathring",tag:"mover",output:"\u00B0",ttype:UNARY,acc:true},{input:"\\vec",tag:"mover",output:"\u20D7",ttype:UNARY,acc:true},{input:"\\overrightarrow",tag:"mover",output:"\u20D7",ttype:UNARY,acc:true},{input:"\\overleftarrow",tag:"mover",output:"\u20D6",ttype:UNARY,acc:true},{input:"\\hat",tag:"mover",output:"\u005E",ttype:UNARY,acc:true},{input:"\\widehat",tag:"mover",output:"\u0302",ttype:UNARY,acc:true},{input:"\\tilde",tag:"mover",output:"~",ttype:UNARY,acc:true},{input:"\\widetilde",tag:"mover",output:"\u02DC",ttype:UNARY,acc:true},{input:"\\bar",tag:"mover",output:"\u203E",ttype:UNARY,acc:true},{input:"\\overbrace",tag:"mover",output:"\uFE37",ttype:UNARY,acc:true},{input:"\\overbracket",tag:"mover",output:"\u23B4",ttype:UNARY,acc:true},{input:"\\overline",tag:"mover",output:"\u00AF",ttype:UNARY,acc:true},{input:"\\underbrace",tag:"munder",output:"\uFE38",ttype:UNARY,acc:true},{input:"\\underbracket",tag:"munder",output:"\u23B5",ttype:UNARY,acc:true},{input:"\\underline",tag:"munder",output:"\u00AF",ttype:UNARY,acc:true},{input:"\\displaystyle",tag:"mstyle",atname:"displaystyle",atval:"true",ttype:UNARY},{input:"\\textstyle",tag:"mstyle",atname:"displaystyle",atval:"false",ttype:UNARY},{input:"\\scriptstyle",tag:"mstyle",atname:"scriptlevel",atval:"1",ttype:UNARY},{input:"\\scriptscriptstyle",tag:"mstyle",atname:"scriptlevel",atval:"2",ttype:UNARY},{input:"\\textrm",tag:"mstyle",output:"\\mathrm",ttype:DEFINITION},{input:"\\mathbf",tag:"mstyle",atname:"mathvariant",atval:"bold",ttype:UNARY},{input:"\\textbf",tag:"mstyle",atname:"mathvariant",atval:"bold",ttype:UNARY},{input:"\\mathit",tag:"mstyle",atname:"mathvariant",atval:"italic",ttype:UNARY},{input:"\\textit",tag:"mstyle",atname:"mathvariant",atval:"italic",ttype:UNARY},{input:"\\mathtt",tag:"mstyle",atname:"mathvariant",atval:"monospace",ttype:UNARY},{input:"\\texttt",tag:"mstyle",atname:"mathvariant",atval:"monospace",ttype:UNARY},{input:"\\mathsf",tag:"mstyle",atname:"mathvariant",atval:"sans-serif",ttype:UNARY},{input:"\\mathbb",tag:"mstyle",atname:"mathvariant",atval:"double-struck",ttype:UNARY,codes:AMbbb},{input:"\\mathcal",tag:"mstyle",atname:"mathvariant",atval:"script",ttype:UNARY,codes:AMcal},{input:"\\mathfrak",tag:"mstyle",atname:"mathvariant",atval:"fraktur",ttype:UNARY,codes:AMfrk},{input:"\\textcolor",tag:"mstyle",atname:"mathvariant",atval:"mathcolor",ttype:BINARY},{input:"\\colorbox",tag:"mstyle",atname:"mathvariant",atval:"background",ttype:BINARY}];function compareNames(s1,s2){if(s1.input>s2.input)return 1 -else return-1;} -var AMnames=[];function AMinitSymbols(){AMsymbols.sort(compareNames);for(i=0;i>1;if(arr[m]=AMnames[k];} -AMpreviousSymbol=AMcurrentSymbol;if(match!=""){AMcurrentSymbol=AMsymbols[mk].ttype;return AMsymbols[mk];} -AMcurrentSymbol=CONST;k=1;st=str.slice(0,1);if("0"<=st&&st<="9")tagst="mn";else tagst=(("A">st||st>"Z")&&("a">st||st>"z")?"mo":"mi");return{input:st,tag:tagst,output:st,ttype:CONST};} -var AMpreviousSymbol,AMcurrentSymbol;function AMparseSexpr(str){var symbol,node,result,result2,i,st,newFrag=document.createDocumentFragment();str=AMremoveCharsAndBlanks(str,0);symbol=AMgetSymbol(str);if(symbol==null||symbol.ttype==RIGHTBRACKET) -return[null,str,null];if(symbol.ttype==DEFINITION){str=symbol.output+AMremoveCharsAndBlanks(str,symbol.input.length);symbol=AMgetSymbol(str);if(symbol==null||symbol.ttype==RIGHTBRACKET) -return[null,str,null];} -str=AMremoveCharsAndBlanks(str,symbol.input.length);switch(symbol.ttype){case SPACE:node=AMcreateElementMathML(symbol.tag);node.setAttribute(symbol.atname,symbol.atval);return[node,str,symbol.tag];case UNDEROVER:if(isIE){if(symbol.input.substr(0,4)=="\\big"){str="\\"+symbol.input.substr(4)+str;symbol=AMgetSymbol(str);symbol.ttype=UNDEROVER;str=AMremoveCharsAndBlanks(str,symbol.input.length);}} -return[AMcreateMmlNode(symbol.tag,document.createTextNode(symbol.output)),str,symbol.tag];case CONST:var output=symbol.output;if(isIE){if(symbol.input=="'") -output="\u2032";else if(symbol.input=="''") -output="\u2033";else if(symbol.input=="'''") -output="\u2033\u2032";else if(symbol.input=="''''") -output="\u2033\u2033";else if(symbol.input=="\\square") -output="\u25A1";else if(symbol.input.substr(0,5)=="\\frac"){var denom=symbol.input.substr(6,1);if(denom=="5"||denom=="6"){str=symbol.input.replace(/\\frac/,"\\frac ")+str;return[node,str,symbol.tag];}}} -node=AMcreateMmlNode(symbol.tag,document.createTextNode(output));return[node,str,symbol.tag];case LONG:node=AMcreateMmlNode(symbol.tag,document.createTextNode(symbol.output));node.setAttribute("minsize","1.5");node.setAttribute("maxsize","1.5");node=AMcreateMmlNode("mover",node);node.appendChild(AMcreateElementMathML("mspace"));return[node,str,symbol.tag];case STRETCHY:if(isIE&&symbol.input=="\\backslash") -symbol.output="\\";node=AMcreateMmlNode(symbol.tag,document.createTextNode(symbol.output));if(symbol.input=="|"||symbol.input=="\\vert"||symbol.input=="\\|"||symbol.input=="\\Vert"){node.setAttribute("lspace","0em");node.setAttribute("rspace","0em");} -node.setAttribute("maxsize",symbol.atval);if(symbol.rtag!=null) -return[node,str,symbol.rtag];else -return[node,str,symbol.tag];case BIG:var atval=symbol.atval;if(isIE) -atval=symbol.ieval;symbol=AMgetSymbol(str);if(symbol==null) -return[null,str,null];str=AMremoveCharsAndBlanks(str,symbol.input.length);node=AMcreateMmlNode(symbol.tag,document.createTextNode(symbol.output));if(isIE){var space=AMcreateElementMathML("mspace");space.setAttribute("height",atval+"ex");node=AMcreateMmlNode("mrow",node);node.appendChild(space);}else{node.setAttribute("minsize",atval);node.setAttribute("maxsize",atval);} -return[node,str,symbol.tag];case LEFTBRACKET:if(symbol.input=="\\left"){symbol=AMgetSymbol(str);if(symbol!=null){if(symbol.input==".") -symbol.invisible=true;str=AMremoveCharsAndBlanks(str,symbol.input.length);}} -result=AMparseExpr(str,true,false);if(symbol==null||(typeof symbol.invisible=="boolean"&&symbol.invisible)) -node=AMcreateMmlNode("mrow",result[0]);else{node=AMcreateMmlNode("mo",document.createTextNode(symbol.output));node=AMcreateMmlNode("mrow",node);node.appendChild(result[0]);} -return[node,result[1],result[2]];case MATRIX:if(symbol.input=="\\begin{array}"){var mask="";symbol=AMgetSymbol(str);str=AMremoveCharsAndBlanks(str,0);if(symbol==null) -mask="l";else{str=AMremoveCharsAndBlanks(str,symbol.input.length);if(symbol.input!="{") -mask="l";else do{symbol=AMgetSymbol(str);if(symbol!=null){str=AMremoveCharsAndBlanks(str,symbol.input.length);if(symbol.input!="}") -mask=mask+symbol.input;}}while(symbol!=null&&symbol.input!=""&&symbol.input!="}");} -result=AMparseExpr("{"+str,true,true);node=AMcreateMmlNode("mtable",result[0]);mask=mask.replace(/l/g,"left ");mask=mask.replace(/r/g,"right ");mask=mask.replace(/c/g,"center ");node.setAttribute("columnalign",mask);node.setAttribute("displaystyle","false");if(isIE) -return[node,result[1],null];var lspace=AMcreateElementMathML("mspace");lspace.setAttribute("width","0.167em");var rspace=AMcreateElementMathML("mspace");rspace.setAttribute("width","0.167em");var node1=AMcreateMmlNode("mrow",lspace);node1.appendChild(node);node1.appendChild(rspace);return[node1,result[1],null];}else{result=AMparseExpr("{"+str,true,true);node=AMcreateMmlNode("mtable",result[0]);if(isIE) -node.setAttribute("columnspacing","0.25em");else -node.setAttribute("columnspacing","0.167em");node.setAttribute("columnalign","right center left");node.setAttribute("displaystyle","true");node=AMcreateMmlNode("mrow",node);return[node,result[1],null];} -case TEXT:if(str.charAt(0)=="{")i=str.indexOf("}");else i=0;if(i==-1) -i=str.length;st=str.slice(1,i);if(st.charAt(0)==" "){node=AMcreateElementMathML("mspace");node.setAttribute("width","0.33em");newFrag.appendChild(node);} -newFrag.appendChild(AMcreateMmlNode(symbol.tag,document.createTextNode(st)));if(st.charAt(st.length-1)==" "){node=AMcreateElementMathML("mspace");node.setAttribute("width","0.33em");newFrag.appendChild(node);} -str=AMremoveCharsAndBlanks(str,i+1);return[AMcreateMmlNode("mrow",newFrag),str,null];case UNARY:result=AMparseSexpr(str);if(result[0]==null)return[AMcreateMmlNode(symbol.tag,document.createTextNode(symbol.output)),str];if(typeof symbol.func=="boolean"&&symbol.func){st=str.charAt(0);if(st=="^"||st=="_"||st==","){return[AMcreateMmlNode(symbol.tag,document.createTextNode(symbol.output)),str,symbol.tag];}else{node=AMcreateMmlNode("mrow",AMcreateMmlNode(symbol.tag,document.createTextNode(symbol.output)));if(isIE){var space=AMcreateElementMathML("mspace");space.setAttribute("width","0.167em");node.appendChild(space);} -node.appendChild(result[0]);return[node,result[1],symbol.tag];}} -if(symbol.input=="\\sqrt"){if(isIE){var space=AMcreateElementMathML("mspace");space.setAttribute("height","1.2ex");space.setAttribute("width","0em");node=AMcreateMmlNode(symbol.tag,result[0]) -node.appendChild(space);return[node,result[1],symbol.tag];}else -return[AMcreateMmlNode(symbol.tag,result[0]),result[1],symbol.tag];}else if(typeof symbol.acc=="boolean"&&symbol.acc){node=AMcreateMmlNode(symbol.tag,result[0]);var output=symbol.output;if(isIE){if(symbol.input=="\\hat") -output="\u0302";else if(symbol.input=="\\widehat") -output="\u005E";else if(symbol.input=="\\bar") -output="\u00AF";else if(symbol.input=="\\grave") -output="\u0300";else if(symbol.input=="\\tilde") -output="\u0303";} -var node1=AMcreateMmlNode("mo",document.createTextNode(output));if(symbol.input=="\\vec"||symbol.input=="\\check") -node1.setAttribute("maxsize","1.2");if(isIE&&symbol.input=="\\bar") -node1.setAttribute("maxsize","0.5");if(symbol.input=="\\underbrace"||symbol.input=="\\underline") -node1.setAttribute("accentunder","true");else -node1.setAttribute("accent","true");node.appendChild(node1);if(symbol.input=="\\overbrace"||symbol.input=="\\underbrace") -node.ttype=UNDEROVER;return[node,result[1],symbol.tag];}else{if(!isIE&&typeof symbol.codes!="undefined"){for(i=0;i64&&st.charCodeAt(j)<91)newst=newst+ -String.fromCharCode(symbol.codes[st.charCodeAt(j)-65]);else newst=newst+st.charAt(j);if(result[0].nodeName=="mi") -result[0]=AMcreateElementMathML("mo").appendChild(document.createTextNode(newst));else result[0].replaceChild(AMcreateElementMathML("mo").appendChild(document.createTextNode(newst)),result[0].childNodes[i]);}} -node=AMcreateMmlNode(symbol.tag,result[0]);node.setAttribute(symbol.atname,symbol.atval);if(symbol.input=="\\scriptstyle"||symbol.input=="\\scriptscriptstyle") -node.setAttribute("displaystyle","false");return[node,result[1],symbol.tag];} -case BINARY:result=AMparseSexpr(str);if(result[0]==null)return[AMcreateMmlNode("mo",document.createTextNode(symbol.input)),str,null];result2=AMparseSexpr(result[1]);if(result2[0]==null)return[AMcreateMmlNode("mo",document.createTextNode(symbol.input)),str,null];if(symbol.input=="\\textcolor"||symbol.input=="\\colorbox"){var tclr=str.match(/\{\s*([#\w]+)\s*\}/);str=str.replace(/\{\s*[#\w]+\s*\}/,"");if(tclr!=null){if(IsColorName.test(tclr[1].toLowerCase())){tclr=LaTeXColor[tclr[1].toLowerCase()];}else{tclr=tclr[1];} -node=AMcreateElementMathML("mstyle");node.setAttribute(symbol.atval,tclr);node.appendChild(result2[0]);return[node,result2[1],symbol.tag];}} -if(symbol.input=="\\root"||symbol.input=="\\stackrel")newFrag.appendChild(result2[0]);newFrag.appendChild(result[0]);if(symbol.input=="\\frac")newFrag.appendChild(result2[0]);return[AMcreateMmlNode(symbol.tag,newFrag),result2[1],symbol.tag];case INFIX:str=AMremoveCharsAndBlanks(str,symbol.input.length);return[AMcreateMmlNode("mo",document.createTextNode(symbol.output)),str,symbol.tag];default:return[AMcreateMmlNode(symbol.tag,document.createTextNode(symbol.output)),str,symbol.tag];}} -function AMparseIexpr(str){var symbol,sym1,sym2,node,result,tag,underover;str=AMremoveCharsAndBlanks(str,0);sym1=AMgetSymbol(str);result=AMparseSexpr(str);node=result[0];str=result[1];tag=result[2];symbol=AMgetSymbol(str);if(symbol.ttype==INFIX){str=AMremoveCharsAndBlanks(str,symbol.input.length);result=AMparseSexpr(str);if(result[0]==null) -result[0]=AMcreateMmlNode("mo",document.createTextNode("\u25A1"));str=result[1];tag=result[2];if(symbol.input=="_"||symbol.input=="^"){sym2=AMgetSymbol(str);tag=null;underover=((sym1.ttype==UNDEROVER)||(node.ttype==UNDEROVER));if(symbol.input=="_"&&sym2.input=="^"){str=AMremoveCharsAndBlanks(str,sym2.input.length);var res2=AMparseSexpr(str);str=res2[1];tag=res2[2];node=AMcreateMmlNode((underover?"munderover":"msubsup"),node);node.appendChild(result[0]);node.appendChild(res2[0]);}else if(symbol.input=="_"){node=AMcreateMmlNode((underover?"munder":"msub"),node);node.appendChild(result[0]);}else{node=AMcreateMmlNode((underover?"mover":"msup"),node);node.appendChild(result[0]);} -node=AMcreateMmlNode("mrow",node);}else{node=AMcreateMmlNode(symbol.tag,node);if(symbol.input=="\\atop"||symbol.input=="\\choose") -node.setAttribute("linethickness","0ex");node.appendChild(result[0]);if(symbol.input=="\\choose") -node=AMcreateMmlNode("mfenced",node);}} -return[node,str,tag];} -function AMparseExpr(str,rightbracket,matrix){var symbol,node,result,i,tag,newFrag=document.createDocumentFragment();do{str=AMremoveCharsAndBlanks(str,0);result=AMparseIexpr(str);node=result[0];str=result[1];tag=result[2];symbol=AMgetSymbol(str);if(node!=undefined){if((tag=="mn"||tag=="mi")&&symbol!=null&&typeof symbol.func=="boolean"&&symbol.func){var space=AMcreateElementMathML("mspace");space.setAttribute("width","0.167em");node=AMcreateMmlNode("mrow",node);node.appendChild(space);} -newFrag.appendChild(node);}}while((symbol.ttype!=RIGHTBRACKET)&&symbol!=null&&symbol.output!="");tag=null;if(symbol.ttype==RIGHTBRACKET){if(symbol.input=="\\right"){str=AMremoveCharsAndBlanks(str,symbol.input.length);symbol=AMgetSymbol(str);if(symbol!=null&&symbol.input==".") -symbol.invisible=true;if(symbol!=null) -tag=symbol.rtag;} -if(symbol!=null) -str=AMremoveCharsAndBlanks(str,symbol.input.length);var len=newFrag.childNodes.length;if(matrix&&len>0&&newFrag.childNodes[len-1].nodeName=="mrow"&&len>1&&newFrag.childNodes[len-2].nodeName=="mo"&&newFrag.childNodes[len-2].firstChild.nodeValue=="&"){var pos=[];var m=newFrag.childNodes.length;for(i=0;matrix&&i2){newFrag.removeChild(newFrag.firstChild);newFrag.removeChild(newFrag.firstChild);} -table.appendChild(AMcreateMmlNode("mtr",row));} -return[table,str];} -if(typeof symbol.invisible!="boolean"||!symbol.invisible){node=AMcreateMmlNode("mo",document.createTextNode(symbol.output));newFrag.appendChild(node);}} -return[newFrag,str,tag];} -function AMparseMath(str){var result,node=AMcreateElementMathML("mstyle");var cclr=str.match(/\\color\s*\{\s*([#\w]+)\s*\}/);str=str.replace(/\\color\s*\{\s*[#\w]+\s*\}/g,"");if(cclr!=null){if(IsColorName.test(cclr[1].toLowerCase())){cclr=LaTeXColor[cclr[1].toLowerCase()];}else{cclr=cclr[1];} -node.setAttribute("mathcolor",cclr);}else{if(mathcolor!="")node.setAttribute("mathcolor",mathcolor);};if(mathfontfamily!="")node.setAttribute("fontfamily",mathfontfamily);node.appendChild(AMparseExpr(str.replace(/^\s+/g,""),false,false)[0]);node=AMcreateMmlNode("math",node);if(showasciiformulaonhover) -node.setAttribute("title",str.replace(/\s+/g," "));if(false){var fnode=AMcreateElementXHTML("font");fnode.setAttribute("face",mathfontfamily);fnode.appendChild(node);return fnode;} -return node;} -function AMstrarr2docFrag(arr,linebreaks){var newFrag=document.createDocumentFragment();var expr=false;for(var i=0;i1||mtch){if(checkForMathML){checkForMathML=false;var nd=AMisMathMLavailable();AMnoMathML=nd!=null;if(AMnoMathML&¬ifyIfNoMathML) -if(alertIfNoMathML) -alert("To view the ASCIIMathML notation use Internet Explorer 6 +\nMathPlayer (free from www.dessci.com)\nor Firefox/Mozilla/Netscape");else AMbody.insertBefore(nd,AMbody.childNodes[0]);} -if(!AMnoMathML){frg=AMstrarr2docFrag(arr,n.nodeType==8);var len=frg.childNodes.length;n.parentNode.replaceChild(frg,n);return len-1;}else return 0;}}}else return 0;}else if(n.nodeName!="math"){for(i=0;i0){if(inAppendix){return"A"+sectionCntr+"."+cntr;}else{return sectionCntr+"."+cntr;}}else{return""+cntr;}};function LaTeXpreProcess(thebody){var TheBody=thebody;if(TheBody.hasChildNodes()){if(!(IsLaTeXElement.test(TheBody.className))) -{for(var i=0;i");str=str.replace(/%[^\n]*(?=\n)/g,"");str=str.replace(/%[^\r]*(?=\r)/g,"");str=str.replace(/%[^\n]*$/,"") -if(isIE&&str.match(/%/g)!=null&&IEcommentWarning){alert("Comments may not have parsed properly. Try putting in
=0){str[i]=str[i].replace(/\\section\s*\{/," \\[section\\]");var delimcnt=1;for(var ii=sectionIndex;ii=0){str[i]=str[i].replace(/\\subsection\s*\{/," \\[subsection\\]");var delimcnt=1;for(var ii=sectionIndex;ii=0){str[i]=str[i].replace(/\\subsubsection\s*\{/," \\[subsubsection\\]");var delimcnt=1;for(var ii=sectionIndex;ii=0){var tmp=strtmparray[1];var delimcnt=0;var capstart=-1;for(var pos=capIndex;pos0){capend=pos-1;FIGcap=tmp.substring(capstart,pos);break}}}
-var FIGtr2=document.createElement("tr");var FIGtd2=document.createElement("td");FIGtd2.className="caption";var FIGanchor=document.createElement("a");FIGanchor.className="figure";if(FIGlbl!=null){FIGanchor.id=FIGlbl[1];}
-LaTeXCounter["figure"]++;var fignmbr=makeNumberString(LaTeXCounter["figure"]);var anchorSpan=document.createElement("span");anchorSpan.className="figure";anchorSpan.style.display="none";anchorSpan.appendChild(document.createTextNode(fignmbr));FIGanchor.appendChild(anchorSpan);FIGtd2.appendChild(FIGanchor);var FIGspan=document.createElement("span");FIGspan.className="figure";FIGspan.appendChild(document.createTextNode("Figure "+fignmbr+". "));FIGtd2.appendChild(FIGspan);FIGtd2.appendChild(document.createTextNode(""+FIGcap));FIGtr2.appendChild(FIGtd2);FIGtbody.appendChild(FIGtr2);var IsSpecial=false;var FIGinfo=strtmparray[1].match(/\\includegraphics\s*\{([^\}]+)\}/);if(FIGinfo==null){FIGinfo=strtmparray[1].match(/\\includegraphics\s*\[[^\]]*\]\s*\{\s*([^\}]+)\s*\}/);}
-if(FIGinfo==null){FIGinfo=strtmparray[1].match(/\\special\s*\{\s*([^\}]+)\}/);IsSpecial=true};if(FIGinfo!=null){var FIGtr1=document.createElement("tr");var FIGtd1=document.createElement("td");FIGtd1.className="image";var FIGimg=document.createElement("img");var FIGsrc=FIGinfo[1];FIGimg.src=FIGsrc;FIGimg.alt="Figure "+FIGsrc+" did not load";FIGimg.title="Figure "+fignmbr+". "+FIGcap;FIGimg.id="figure"+fignmbr;FIGtd1.appendChild(FIGimg);FIGtr1.appendChild(FIGtd1);FIGtbody.appendChild(FIGtr1);}
-nodeTmp.appendChild(FIGtbody);newFrag.appendChild(nodeTmp);break;case"table":var nodeTmp=document.createElement("table");if(strtmparray[1].search(/\\centering/)>=0){nodeTmp.className='LaTeXtable centered';nodeTmp.align="center";}else{nodeTmp.className='LaTeXtable';};tableid++;nodeTmp.id="LaTeXtable"+tableid;var TABlbl=strtmparray[1].match(/\\label\s*\{\s*(\w+)\s*\}/);strtmparray[1]=strtmparray[1].replace(/\\label\s*\{\w+\}/g,"");var capIndex=strtmparray[1].search(/\\caption\s*\{[\s\S]+\}/);var TABcap="";if(capIndex>=0){var tmp=strtmparray[1];var delimcnt=0;var capstart=-1;for(var pos=capIndex;pos0){capend=pos-1;TABcap=tmp.substring(capstart,pos);break}}}
-if(TABcap!=""){var TABtbody=document.createElement("tbody");var TABcaption=document.createElement("caption");TABcaption.className="LaTeXtable centered";var TABanchor=document.createElement("a");TABanchor.className="LaTeXtable";if(TABlbl!=null){TABanchor.id=TABlbl[1];}
-LaTeXCounter["table"]++;var tabnmbr=makeNumberString(LaTeXCounter["table"]);var anchorSpan=document.createElement("span");anchorSpan.className="LaTeXtable";anchorSpan.style.display="none";anchorSpan.appendChild(document.createTextNode(tabnmbr));TABanchor.appendChild(anchorSpan);TABcaption.appendChild(TABanchor);var TABspan=document.createElement("span");TABspan.className="LaTeXtable";TABspan.appendChild(document.createTextNode("Table "+tabnmbr+". "));TABcaption.appendChild(TABspan);TABcaption.appendChild(document.createTextNode(""+TABcap));nodeTmp.appendChild(TABcaption);}
-var TABinfo=strtmparray[1].match(/\\begin\s*\{\s*tabular\s*\}([\s\S]+)\\end\s*\{\s*tabular\s*\}/);if(TABinfo!=null){var TABtbody=document.createElement('tbody');var TABrow=null;var TABcell=null;var row=0;var col=0;var TABalign=TABinfo[1].match(/^\s*\{([^\}]+)\}/);TABinfo=TABinfo[1].replace(/^\s*\{[^\}]+\}/,"");TABinfo=TABinfo.replace(/\\hline/g,"");TABalign[1]=TABalign[1].replace(/\|/g,"");TABalign[1]=TABalign[1].replace(/\s/g,"");TABinfo=TABinfo.split("\\\\");for(row=0;row");strtmp[j]=strtmp[j].replace(/\$([^\$]+)\$/g," \\[$1\\[ ");strtmp[j]=strtmp[j].replace(//g,"\\$");strtmp[j]=strtmp[j].replace(/\\begin\s*\{\s*math\s*\}([\s\S]+?)\\end\s*\{\s*math\s*\}/g," \\[$1\\[ ");var strtmptmp=strtmp[j].split("\\[");for(var jjj=0;jjj-1){if(/^\\textcolor/.test(strtmptmp[jjj].substring(TagIndex,strtmptmp[jjj].length))){strtmptmp[jjj]=strtmptmp[jjj].replace(/\\textcolor\s*\{\s*(\w+)\s*\}\s*/," \\[textcolor\\]$1\\]|");}else{if(/^\\colorbox/.test(strtmptmp[jjj].substring(TagIndex,strtmptmp[jjj].length))){strtmptmp[jjj]=strtmptmp[jjj].replace(/\\colorbox\s*\{\s*(\w+)\s*\}\s*/," \\[colorbox\\]$1\\]|");}else{strtmptmp[jjj]=strtmptmp[jjj].substring(0,TagIndex)+strtmptmp[jjj].substring(TagIndex,strtmptmp[jjj].length).replace(/\\\s*(\w+)\s*/," \\[$1\\]|");}}
-TagIndex+=strtmptmp[jjj].substring(TagIndex,strtmptmp[jjj].length).search(/\|/);TagIndex++;strtmptmp[jjj]=strtmptmp[jjj].replace(/\\\]\|/,"\\] ");if(strtmptmp[jjj].charAt(TagIndex)=="{"){strtmptmp[jjj]=strtmptmp[jjj].substring(0,TagIndex)+strtmptmp[jjj].substring(TagIndex+1,strtmptmp[jjj].length);var delimcnt=1;for(var kk=TagIndex;kk=0;i--){EndDivClass=AllDivs[i].className.match(/end\w+/);if(EndDivClass!=null){EndDivClass=EndDivClass[0];var DivClass=EndDivClass.substring(3,EndDivClass.length);var EndDivNode=AllDivs[i];break;}}
-while(EndDivClass!=null){var newFrag=document.createDocumentFragment();var RootNode=EndDivNode.parentNode;var ClassCount=1;while(EndDivNode.previousSibling!=null&&ClassCount>0){switch(EndDivNode.previousSibling.className){case EndDivClass:ClassCount++;newFrag.insertBefore(EndDivNode.previousSibling,newFrag.firstChild);break;case DivClass:if(EndDivNode.previousSibling.nodeName=="DIV"){ClassCount--;if(lbl2id!=""){EndDivNode.previousSibling.id=lbl2id;lbl2id=""}
-if(ClassCount==0){RootNode=EndDivNode.previousSibling;}else{newFrag.insertBefore(EndDivNode.previousSibling,newFrag.firstChild);}};break;case'LaTeXMathMLlabel':lbl2id=EndDivNode.previousSibling.id;EndDivNode.parentNode.removeChild(EndDivNode.previousSibling);break;default:newFrag.insertBefore(EndDivNode.previousSibling,newFrag.firstChild);}}
-RootNode.appendChild(newFrag);EndDivNode.parentNode.removeChild(EndDivNode);AllDivs=TheBody.getElementsByTagName("DIV");for(i=AllDivs.length-1;i>=0;i--){EndDivClass=AllDivs[i].className.match(/end\w+/);if(EndDivClass!=null){ClassCount=0;EndDivClass=EndDivClass[0];DivClass=EndDivClass.substring(3,EndDivClass.length);EndDivNode=AllDivs[i];RootNode=EndDivNode.parentNode;break;}}}
-var AllDivs=TheBody.getElementsByTagName("div");var DIV2LI=null;for(var i=0;i0){for(var m=0;m");document.write("");}
-function generic()
-{translate();};if(typeof window.addEventListener!='undefined')
-{window.addEventListener('load',generic,false);}
-else if(typeof document.addEventListener!='undefined')
-{document.addEventListener('load',generic,false);}
-else if(typeof window.attachEvent!='undefined')
-{window.attachEvent('onload',generic);}
-else
-{if(typeof window.onload=='function')
-{var existing=onload;window.onload=function()
-{existing();generic();};}
-else
-{window.onload=generic;}}
diff --git a/pandoc.cabal b/pandoc.cabal
index e656e451c..24fba87f7 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -1,5 +1,5 @@
 name:            pandoc
-version:         2.1.4
+version:         2.2
 cabal-version:   >= 1.10
 build-type:      Custom
 license:         GPL-2
@@ -148,8 +148,6 @@ data-files:
                  data/pptx/[Content_Types].xml
                   -- stylesheet for EPUB writer
                  data/epub.css
-                 -- data for LaTeXMathML writer
-                 data/LaTeXMathML.js
                  -- data for dzslides writer
                  data/dzslides/template.html
                  -- default abbreviations file
diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs
index b124bdda0..e9778fffc 100644
--- a/src/Text/Pandoc/App.hs
+++ b/src/Text/Pandoc/App.hs
@@ -357,12 +357,6 @@ convertWithOpts opts = do
         maybe return (addStringAsVariable "epub-cover-image")
                      (optEpubCoverImage opts)
         >>=
-        (\vars -> case optHTMLMathMethod opts of
-                       LaTeXMathML Nothing -> do
-                          s <- UTF8.toString <$> readDataFile "LaTeXMathML.js"
-                          return $ ("mathml-script", s) : vars
-                       _ -> return vars)
-        >>=
         (\vars ->  if format == "dzslides"
                       then do
                           dztempl <- UTF8.toString <$> readDataFile
@@ -1401,40 +1395,6 @@ options =
                   "URL")
                   "" -- Use KaTeX for HTML Math
 
-    , Option "m" ["latexmathml", "asciimathml"]
-                 (OptArg
-                  (\arg opt -> do
-                      deprecatedOption "--latexmathml, --asciimathml, -m" ""
-                      return opt { optHTMLMathMethod = LaTeXMathML arg })
-                  "URL")
-                 "" -- "Use LaTeXMathML script in html output"
-
-    , Option "" ["mimetex"]
-                 (OptArg
-                  (\arg opt -> do
-                      deprecatedOption "--mimetex" ""
-                      let url' = case arg of
-                                      Just u  -> u ++ "?"
-                                      Nothing -> "/cgi-bin/mimetex.cgi?"
-                      return opt { optHTMLMathMethod = WebTeX url' })
-                  "URL")
-                 "" -- "Use mimetex for HTML math"
-
-    , Option "" ["jsmath"]
-                 (OptArg
-                  (\arg opt -> do
-                      deprecatedOption "--jsmath" ""
-                      return opt { optHTMLMathMethod = JsMath arg})
-                  "URL")
-                 "" -- "Use jsMath for HTML math"
-
-    , Option "" ["gladtex"]
-                 (NoArg
-                  (\opt -> do
-                      deprecatedOption "--gladtex" ""
-                      return opt { optHTMLMathMethod = GladTeX }))
-                 "" -- "Use gladtex for HTML math"
-
     , Option "" ["abbreviations"]
                 (ReqArg
                  (\arg opt -> return opt { optAbbreviations = Just arg })
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs
index a542954ad..4797a3094 100644
--- a/src/Text/Pandoc/Options.hs
+++ b/src/Text/Pandoc/Options.hs
@@ -106,9 +106,6 @@ defaultAbbrevs = Set.fromList
 data EPUBVersion = EPUB2 | EPUB3 deriving (Eq, Show, Read, Data, Typeable, Generic)
 
 data HTMLMathMethod = PlainMath
-                    | LaTeXMathML (Maybe String)  -- url of LaTeXMathML.js
-                    | JsMath (Maybe String)       -- url of jsMath load script
-                    | GladTeX
                     | WebTeX String               -- url of TeX->image script.
                     | MathML
                     | MathJax String              -- url of MathJax.js
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index d1a366445..762bbd0e5 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -260,10 +260,6 @@ pandocToHtml opts (Pandoc meta blocks) = do
   notes <- footnoteSection opts (reverse (stNotes st))
   let thebody = blocks' >> notes
   let  math = case writerHTMLMathMethod opts of
-                      LaTeXMathML (Just url) ->
-                         H.script ! A.src (toValue url)
-                                  ! A.type_ "text/javascript"
-                                  $ mempty
                       MathJax url
                         | slideVariant /= RevealJsSlides ->
                         -- mathjax is handled via a special plugin in revealjs
@@ -274,10 +270,6 @@ pandocToHtml opts (Pandoc meta blocks) = do
                                             preEscapedString
                                             "MathJax.Hub.Queue([\"Typeset\",MathJax.Hub]);"
                                          _ -> mempty
-                      JsMath (Just url) ->
-                         H.script ! A.src (toValue url)
-                                  ! A.type_ "text/javascript"
-                                  $ mempty
                       KaTeX url -> do
                          H.script !
                            A.src (toValue $ url ++ "katex.min.js") $ mempty
@@ -1024,19 +1016,6 @@ inlineToHtml opts inline = do
       let mathClass = toValue $ ("math " :: String) ++
                       if t == InlineMath then "inline" else "display"
       case writerHTMLMathMethod opts of
-           LaTeXMathML _ ->
-              -- putting LaTeXMathML in container with class "LaTeX" prevents
-              -- non-math elements on the page from being treated as math by
-              -- the javascript
-              return $ H.span ! A.class_ "LaTeX" $
-                     case t of
-                       InlineMath  -> toHtml ("$" ++ str ++ "$")
-                       DisplayMath -> toHtml ("$$" ++ str ++ "$$")
-           JsMath _ -> do
-              let m = preEscapedString str
-              return $ case t of
-                       InlineMath  -> H.span ! A.class_ mathClass $ m
-                       DisplayMath -> H.div ! A.class_ mathClass $ m
            WebTeX url -> do
               let imtag = if html5 then H5.img else H.img
               let m = imtag ! A.style "vertical-align:middle"
@@ -1047,10 +1026,6 @@ inlineToHtml opts inline = do
               return $ case t of
                         InlineMath  -> m
                         DisplayMath -> brtag >> m >> brtag
-           GladTeX ->
-              return $ case t of
-                         InlineMath -> preEscapedString $ "" ++ str ++ ""
-                         DisplayMath -> preEscapedString $ "" ++ str ++ ""
            MathML -> do
               let conf = useShortEmptyTags (const False)
                            defaultConfigPP
diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs
index cfca576da..b426ffd07 100644
--- a/test/Tests/Old.hs
+++ b/test/Tests/Old.hs
@@ -59,7 +59,7 @@ tests = [ testGroup "markdown"
           ]
         , testGroup "s5"
           [ s5WriterTest "basic" ["-s"] "s5"
-          , s5WriterTest "fancy" ["-s","-m","-i"] "s5"
+          , s5WriterTest "fancy" ["-s","--mathjax","-i"] "s5"
           , s5WriterTest "fragment" [] "html4"
           , s5WriterTest "inserts"  ["-s", "-H", "insert",
             "-B", "insert", "-A", "insert", "-c", "main.css"] "html4"
diff --git a/test/s5-fancy.html b/test/s5-fancy.html
index 9f724af96..b326f9872 100644
--- a/test/s5-fancy.html
+++ b/test/s5-fancy.html
@@ -26,207 +26,7 @@
   
   
   
-  
+  
 
 
 
@@ -254,7 +54,7 @@

Math

    -
  • $\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$
  • +
  • \(\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}\)
-- cgit v1.2.3 From a9344bf308afa4d2197582aff8045de56e24c7aa Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 25 Apr 2018 17:36:01 -0700 Subject: LaTeX reader: support `\MakeUppercase`, `\MakeLowercase'. Also `\MakeTextUppercase`, `\MakeTextLowercase` from textcase and `\uppercase`, `\lowercase`. We don't mimic exactly the quirky semantic differences between these commands, but just uppercase/lowercase regular strings within them. We leave commands and code alone. Closes #4595. --- src/Text/Pandoc/Readers/LaTeX.hs | 18 +++++++++++++++++- 1 file changed, 17 insertions(+), 1 deletion(-) (limited to 'src') diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index e1497dfb1..6254ce3f3 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -48,7 +48,7 @@ import Control.Applicative (many, optional, (<|>)) import Control.Monad import Control.Monad.Except (throwError) import Control.Monad.Trans (lift) -import Data.Char (chr, isAlphaNum, isDigit, isLetter, ord, toLower) +import Data.Char (chr, isAlphaNum, isDigit, isLetter, ord, toLower, toUpper) import Data.Default import Data.List (intercalate, isPrefixOf) import qualified Data.Map as M @@ -1315,6 +1315,12 @@ inlineCommands = M.union inlineLanguageCommands $ M.fromList , ("slshape", extractSpaces emph <$> inlines) , ("scshape", extractSpaces smallcaps <$> inlines) , ("bfseries", extractSpaces strong <$> inlines) + , ("MakeUppercase", makeUppercase <$> tok) + , ("MakeTextUppercase", makeUppercase <$> tok) -- textcase + , ("uppercase", makeUppercase <$> tok) + , ("MakeLowercase", makeLowercase <$> tok) + , ("MakeTextLowercase", makeLowercase <$> tok) + , ("lowercase", makeLowercase <$> tok) , ("/", pure mempty) -- italic correction , ("aa", lit "å") , ("AA", lit "Å") @@ -1515,6 +1521,16 @@ inlineCommands = M.union inlineLanguageCommands $ M.fromList , ("foreignlanguage", foreignlanguage) ] +makeUppercase :: Inlines -> Inlines +makeUppercase = fromList . walk (alterStr (map toUpper)) . toList + +makeLowercase :: Inlines -> Inlines +makeLowercase = fromList . walk (alterStr (map toLower)) . toList + +alterStr :: (String -> String) -> Inline -> Inline +alterStr f (Str xs) = Str (f xs) +alterStr _ x = x + foreignlanguage :: PandocMonad m => LP m Inlines foreignlanguage = do babelLang <- T.unpack . untokenize <$> braced -- cgit v1.2.3 From 06bc0376d1cc26b254e9f85a5dd7e29c4e969c3c Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 25 Apr 2018 23:20:52 -0700 Subject: LaTeX reader: Improve handling of raw LaTeX (for markdown etc.). Previously there were some bugs in how macros were handled. Closes #4589, #4594. --- src/Text/Pandoc/Readers/LaTeX.hs | 63 ++++++++++++++++++++-------------------- 1 file changed, 32 insertions(+), 31 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index 6254ce3f3..d3d1f6634 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -242,21 +242,30 @@ withVerbatimMode parser = do return result rawLaTeXParser :: (PandocMonad m, HasMacros s, HasReaderOptions s) - => LP m a -> ParserT String s m (a, String) -rawLaTeXParser parser = do + => LP m a -> LP m a -> ParserT String s m (a, String) +rawLaTeXParser parser valParser = do inp <- getInput let toks = tokenize "source" $ T.pack inp pstate <- getState - let lstate = def{ sOptions = extractReaderOptions pstate - , sMacros = extractMacros pstate } - let rawparser = (,) <$> withRaw parser <*> getState - res <- lift $ runParserT rawparser lstate "chunk" toks - case res of + let lstate = def{ sOptions = extractReaderOptions pstate } + let lstate' = lstate { sMacros = extractMacros pstate } + let rawparser = (,) <$> withRaw valParser <*> getState + res' <- lift $ runParserT (snd <$> withRaw parser) lstate "chunk" toks + case res' of Left _ -> mzero - Right ((val, raw), st) -> do - updateState (updateMacros (sMacros st <>)) - rawstring <- takeP (T.length (untokenize raw)) - return (val, rawstring) + Right toks' -> do + res <- lift $ runParserT (do doMacros 0 + -- retokenize, applying macros + ts <- many (satisfyTok (const True)) + setInput ts + rawparser) + lstate' "chunk" toks' + case res of + Left _ -> mzero + Right ((val, raw), st) -> do + updateState (updateMacros (sMacros st <>)) + _ <- takeP (T.length (untokenize toks')) + return (val, T.unpack (untokenize raw)) applyMacros :: (PandocMonad m, HasMacros s, HasReaderOptions s) => String -> ParserT String s m String @@ -277,19 +286,18 @@ rawLaTeXBlock = do lookAhead (try (char '\\' >> letter)) -- we don't want to apply newly defined latex macros to their own -- definitions: - snd <$> rawLaTeXParser macroDef - <|> ((snd <$> rawLaTeXParser (environment <|> blockCommand)) >>= applyMacros) + snd <$> rawLaTeXParser (environment <|> macroDef <|> blockCommand) block rawLaTeXInline :: (PandocMonad m, HasMacros s, HasReaderOptions s) => ParserT String s m String rawLaTeXInline = do lookAhead (try (char '\\' >> letter)) - rawLaTeXParser (inlineEnvironment <|> inlineCommand') >>= applyMacros . snd + snd <$> rawLaTeXParser (inlineEnvironment <|> inlineCommand') inline inlineCommand :: PandocMonad m => ParserT String ParserState m Inlines inlineCommand = do lookAhead (try (char '\\' >> letter)) - fst <$> rawLaTeXParser (inlineEnvironment <|> inlineCommand') + fst <$> rawLaTeXParser (inlineEnvironment <|> inlineCommand') inline tokenize :: SourceName -> Text -> [Tok] tokenize sourcename = totoks (initialPos sourcename) @@ -1703,6 +1711,9 @@ treatAsBlock = Set.fromList , "clearpage" , "pagebreak" , "titleformat" + , "listoffigures" + , "listoftables" + , "write" ] isInlineCommand :: Text -> Bool @@ -2165,19 +2176,6 @@ environments = M.fromList codeBlockWith attr <$> verbEnv "lstlisting") , ("minted", minted) , ("obeylines", obeylines) - , ("displaymath", mathEnvWith para Nothing "displaymath") - , ("equation", mathEnvWith para Nothing "equation") - , ("equation*", mathEnvWith para Nothing "equation*") - , ("gather", mathEnvWith para (Just "gathered") "gather") - , ("gather*", mathEnvWith para (Just "gathered") "gather*") - , ("multline", mathEnvWith para (Just "gathered") "multline") - , ("multline*", mathEnvWith para (Just "gathered") "multline*") - , ("eqnarray", mathEnvWith para (Just "aligned") "eqnarray") - , ("eqnarray*", mathEnvWith para (Just "aligned") "eqnarray*") - , ("align", mathEnvWith para (Just "aligned") "align") - , ("align*", mathEnvWith para (Just "aligned") "align*") - , ("alignat", mathEnvWith para (Just "aligned") "alignat") - , ("alignat*", mathEnvWith para (Just "aligned") "alignat*") , ("tikzpicture", rawVerbEnv "tikzpicture") -- etoolbox , ("ifstrequal", ifstrequal) @@ -2188,11 +2186,14 @@ environments = M.fromList ] environment :: PandocMonad m => LP m Blocks -environment = do +environment = try $ do controlSeq "begin" name <- untokenize <$> braced - M.findWithDefault mzero name environments - <|> rawEnv name + M.findWithDefault mzero name environments <|> + if M.member name (inlineEnvironments + :: M.Map Text (LP PandocPure Inlines)) + then mzero + else rawEnv name env :: PandocMonad m => Text -> LP m a -> LP m a env name p = p <* end_ name -- cgit v1.2.3 From c139a011fa7a4b5bbbcb4b1f277dcb5ee733142f Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 25 Apr 2018 23:47:43 -0700 Subject: LaTeX reader: fixed previous commit. --- src/Text/Pandoc/Readers/LaTeX.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index d3d1f6634..041b552dc 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -286,18 +286,18 @@ rawLaTeXBlock = do lookAhead (try (char '\\' >> letter)) -- we don't want to apply newly defined latex macros to their own -- definitions: - snd <$> rawLaTeXParser (environment <|> macroDef <|> blockCommand) block + snd <$> rawLaTeXParser (environment <|> macroDef <|> blockCommand) blocks rawLaTeXInline :: (PandocMonad m, HasMacros s, HasReaderOptions s) => ParserT String s m String rawLaTeXInline = do lookAhead (try (char '\\' >> letter)) - snd <$> rawLaTeXParser (inlineEnvironment <|> inlineCommand') inline + snd <$> rawLaTeXParser (inlineEnvironment <|> inlineCommand') inlines inlineCommand :: PandocMonad m => ParserT String ParserState m Inlines inlineCommand = do lookAhead (try (char '\\' >> letter)) - fst <$> rawLaTeXParser (inlineEnvironment <|> inlineCommand') inline + fst <$> rawLaTeXParser (inlineEnvironment <|> inlineCommand') inlines tokenize :: SourceName -> Text -> [Tok] tokenize sourcename = totoks (initialPos sourcename) -- cgit v1.2.3 From 188f9f4c53179e474d9538927345583b8e91770e Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Thu, 26 Apr 2018 12:09:25 +0300 Subject: Simplify curSlideHasSpeakerNotes --- src/Text/Pandoc/Writers/Powerpoint/Output.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Writers/Powerpoint/Output.hs b/src/Text/Pandoc/Writers/Powerpoint/Output.hs index dc5f1c9a9..c8a30d010 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Output.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Output.hs @@ -328,10 +328,8 @@ presHasSpeakerNotes :: Presentation -> Bool presHasSpeakerNotes (Presentation _ slides) = not $ all (mempty ==) $ map slideSpeakerNotes slides curSlideHasSpeakerNotes :: PandocMonad m => P m Bool -curSlideHasSpeakerNotes = do - sldId <- asks envCurSlideId - notesIdMap <- asks envSpeakerNotesIdMap - return $ isJust $ M.lookup sldId notesIdMap +curSlideHasSpeakerNotes = + M.member <$> asks envCurSlideId <*> asks envSpeakerNotesIdMap -------------------------------------------------- -- cgit v1.2.3 From 73463b823929ce4930ed60e576d13a148ffb573c Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Thu, 26 Apr 2018 12:09:59 +0300 Subject: Muse reader: use Data.Map.member instead of lookup --- src/Text/Pandoc/Readers/Muse.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs index 43c835edb..f21a169fd 100644 --- a/src/Text/Pandoc/Readers/Muse.hs +++ b/src/Text/Pandoc/Readers/Muse.hs @@ -50,7 +50,7 @@ import Data.List (stripPrefix, intercalate) import Data.List.Split (splitOn) import qualified Data.Map as M import qualified Data.Set as Set -import Data.Maybe (fromMaybe, isJust, isNothing) +import Data.Maybe (fromMaybe, isNothing) import Data.Text (Text, unpack) import System.FilePath (takeExtension) import Text.HTML.TagSoup @@ -515,7 +515,7 @@ amuseNoteBlockUntil end = try $ do updateState (\st -> st { museInPara = False }) (content, e) <- listItemContentsUntil (sourceColumn pos - 1) (fail "x") end oldnotes <- museNotes <$> getState - when (isJust (M.lookup ref oldnotes)) + when (M.member ref oldnotes) (logMessage $ DuplicateNoteReference ref pos) updateState $ \s -> s{ museNotes = M.insert ref (pos, content) oldnotes } return (mempty, e) @@ -529,7 +529,7 @@ emacsNoteBlock = try $ do ref <- noteMarker <* skipSpaces content <- mconcat <$> blocksTillNote oldnotes <- museNotes <$> getState - when (isJust (M.lookup ref oldnotes)) + when (M.member ref oldnotes) (logMessage $ DuplicateNoteReference ref pos) updateState $ \s -> s{ museNotes = M.insert ref (pos, content) oldnotes } return mempty -- cgit v1.2.3 From 4d89a1db7f1ad9d64db7c9e2c294351821ff3993 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Thu, 26 Apr 2018 12:29:45 +0300 Subject: Muse reader: allow nested footnotes --- src/Text/Pandoc/Readers/Muse.hs | 2 +- test/Tests/Readers/Muse.hs | 9 +++++++++ 2 files changed, 10 insertions(+), 1 deletion(-) (limited to 'src') diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs index f21a169fd..fe6b3698c 100644 --- a/src/Text/Pandoc/Readers/Muse.hs +++ b/src/Text/Pandoc/Readers/Muse.hs @@ -821,7 +821,7 @@ footnote = try $ do Nothing -> return $ B.str $ "[" ++ ref ++ "]" Just (_pos, contents) -> do st <- askF - let contents' = runF contents st { museNotes = M.empty } + let contents' = runF contents st { museNotes = M.delete ref (museNotes st) } return $ B.note contents' whitespace :: PandocMonad m => MuseParser m (F Inlines) diff --git a/test/Tests/Readers/Muse.hs b/test/Tests/Readers/Muse.hs index a7eb9d0eb..ecdd5fdb0 100644 --- a/test/Tests/Readers/Muse.hs +++ b/test/Tests/Readers/Muse.hs @@ -659,6 +659,15 @@ tests = ] =?> para (text "Start recursion here" <> note (para "Recursion continues here[1]")) + , "Nested footnotes" =: + T.unlines [ "Footnote: [1]" + , "" + , "[1] Nested: [2]" + , "" + , "[2] No recursion: [1]" + ] =?> + para (text "Footnote: " <> + note (para (text "Nested: " <> note (para $ text "No recursion: [1]")))) , "No zero footnotes" =: T.unlines [ "Here is a footnote[0]." , "" -- cgit v1.2.3 From 1b5948b0797d2161efd1f269c6996d87a6c70af8 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Thu, 26 Apr 2018 14:43:27 +0300 Subject: Remove unused import --- src/Text/Pandoc/Writers/Powerpoint/Output.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) (limited to 'src') diff --git a/src/Text/Pandoc/Writers/Powerpoint/Output.hs b/src/Text/Pandoc/Writers/Powerpoint/Output.hs index c8a30d010..865ef1efc 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Output.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Output.hs @@ -58,7 +58,7 @@ import Text.Pandoc.MIME import qualified Data.ByteString.Lazy as BL import Text.Pandoc.Writers.OOXML import qualified Data.Map as M -import Data.Maybe (mapMaybe, listToMaybe, fromMaybe, isJust, maybeToList, catMaybes) +import Data.Maybe (mapMaybe, listToMaybe, fromMaybe, maybeToList, catMaybes) import Text.Pandoc.ImageSize import Control.Applicative ((<|>)) import System.FilePath.Glob -- cgit v1.2.3 From cfa4eee28bc3d6521f806bc37c937e9615d15588 Mon Sep 17 00:00:00 2001 From: Joe Hermaszewski Date: Fri, 27 Apr 2018 03:12:28 +0800 Subject: DocBook Reader: Read Latex math as output by asciidoctor (#4569) --- src/Text/Pandoc/Readers/DocBook.hs | 59 +++++++++++++++++++++++++++++++------- 1 file changed, 48 insertions(+), 11 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs index 809018697..3d48c7ee8 100644 --- a/src/Text/Pandoc/Readers/DocBook.hs +++ b/src/Text/Pandoc/Readers/DocBook.hs @@ -265,7 +265,7 @@ List of all DocBook tags, with [x] indicating implemented, [ ] manvolnum - A reference volume number [x] markup - A string of formatting markup in text that is to be represented literally -[ ] mathphrase - A mathematical phrase, an expression that can be represented +[x] mathphrase - A mathematical phrase, an expression that can be represented with ordinary text and a small amount of markup [ ] medialabel - A name that identifies the physical medium on which some information resides @@ -727,6 +727,8 @@ parseBlock (Elem e) = "bibliodiv" -> sect 1 "biblioentry" -> parseMixed para (elContent e) "bibliomixed" -> parseMixed para (elContent e) + "equation" -> para <$> equation e displayMath + "informalequation" -> para <$> equation e displayMath "glosssee" -> para . (\ils -> text "See " <> ils <> str ".") <$> getInlines e "glossseealso" -> para . (\ils -> text "See also " <> ils <> str ".") @@ -953,9 +955,9 @@ parseInline (CRef ref) = return $ maybe (text $ map toUpper ref) text $ lookupEntity ref parseInline (Elem e) = case qName (elName e) of - "equation" -> equation displayMath - "informalequation" -> equation displayMath - "inlineequation" -> equation math + "equation" -> equation e displayMath + "informalequation" -> equation e displayMath + "inlineequation" -> equation e math "subscript" -> subscript <$> innerInlines "superscript" -> superscript <$> innerInlines "inlinemediaobject" -> getMediaobject e @@ -1034,13 +1036,6 @@ parseInline (Elem e) = _ -> innerInlines where innerInlines = (trimInlines . mconcat) <$> mapM parseInline (elContent e) - equation constructor = return $ mconcat $ - map (constructor . writeTeX) - $ rights - $ map (readMathML . showElement . everywhere (mkT removePrefix)) - $ filterChildren (\x -> qName (elName x) == "math" && - qPrefix (elName x) == Just "mml") e - removePrefix elname = elname { qPrefix = Nothing } codeWithLang = do let classes' = case attrValue "language" e of "" -> [] @@ -1091,3 +1086,45 @@ parseInline (Elem e) = xrefLabel = attrValue "xreflabel" el descendantContent name = maybe "???" strContent . filterElementName (\n -> qName n == name) + +-- | Extract a math equation from an element +-- +-- asciidoc can generate Latex math in CDATA sections. +-- +-- Note that if some MathML can't be parsed it is silently ignored! +equation + :: Monad m + => Element + -- ^ The element from which to extract a mathematical equation + -> (String -> Inlines) + -- ^ A constructor for some Inlines, taking the TeX code as input + -> m Inlines +equation e constructor = + return $ mconcat $ map constructor $ mathMLEquations ++ latexEquations + where + mathMLEquations :: [String] + mathMLEquations = map writeTeX $ rights $ readMath + (\x -> qName (elName x) == "math" && qPrefix (elName x) == Just "mml") + (readMathML . showElement) + + latexEquations :: [String] + latexEquations = readMath (\x -> qName (elName x) == "mathphrase") + (concat . fmap showVerbatimCData . elContent) + + readMath :: (Element -> Bool) -> (Element -> b) -> [b] + readMath childPredicate fromElement = + ( map (fromElement . everywhere (mkT removePrefix)) + $ filterChildren childPredicate e + ) + +-- | Get the actual text stored in a verbatim CData block. 'showContent' +-- returns the text still surrounded by the [[CDATA]] tags. +-- +-- Returns 'showContent' if this is not a verbatim CData +showVerbatimCData :: Content -> String +showVerbatimCData (Text (CData CDataVerbatim d _)) = d +showVerbatimCData c = showContent c + +-- | Set the prefix of a name to 'Nothing' +removePrefix :: QName -> QName +removePrefix elname = elname { qPrefix = Nothing } -- cgit v1.2.3 From eef1c211f58f0a2ffc6c500bd2158569b83fca1f Mon Sep 17 00:00:00 2001 From: Francesco Occhipinti Date: Thu, 26 Apr 2018 21:17:51 +0200 Subject: RST reader: flatten nested inlines, closes #4368 (#4554) nested inlines are not valid RST syntax, so we flatten them following some readability criteria discussed in #4368. --- src/Text/Pandoc/Writers/RST.hs | 78 ++++++++++++++++++++++++++++++++++++++++-- test/Tests/Writers/RST.hs | 24 +++++++++++++ test/writer.rst | 14 ++++---- 3 files changed, 106 insertions(+), 10 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index cc7131d0a..084615357 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -31,7 +31,7 @@ Conversion of 'Pandoc' documents to reStructuredText. reStructuredText: -} -module Text.Pandoc.Writers.RST ( writeRST ) where +module Text.Pandoc.Writers.RST ( writeRST, flatten ) where import Prelude import Control.Monad.State.Strict import Data.Char (isSpace, toLower) @@ -377,8 +377,10 @@ blockListToRST :: PandocMonad m blockListToRST = blockListToRST' False transformInlines :: [Inline] -> [Inline] -transformInlines = stripLeadingTrailingSpace . insertBS - . filter hasContents . removeSpaceAfterDisplayMath +transformInlines = insertBS . + filter hasContents . + removeSpaceAfterDisplayMath . + concatMap (transformNested . flatten) where -- empty inlines are not valid RST syntax hasContents :: Inline -> Bool hasContents (Str "") = False @@ -412,6 +414,8 @@ transformInlines = stripLeadingTrailingSpace . insertBS x : insertBS (y : zs) insertBS (x:ys) = x : insertBS ys insertBS [] = [] + transformNested :: [Inline] -> [Inline] + transformNested = map (mapNested stripLeadingTrailingSpace) surroundComplex :: Inline -> Inline -> Bool surroundComplex (Str s@(_:_)) (Str s'@(_:_)) = case (last s, head s') of @@ -449,6 +453,74 @@ transformInlines = stripLeadingTrailingSpace . insertBS isComplex (Span _ (x:_)) = isComplex x isComplex _ = False +-- | Flattens nested inlines. Extracts nested inlines and goes through +-- them either collapsing them in the outer inline container or +-- pulling them out of it +flatten :: Inline -> [Inline] +flatten outer = combineAll $ dropInlineParent outer + where combineAll = foldl combine [] + + combine :: [Inline] -> Inline -> [Inline] + combine f i = + case (outer, i) of + -- quotes are not rendered using RST inlines, so we can keep + -- them and they will be readable and parsable + (Quoted _ _, _) -> keep f i + (_, Quoted _ _) -> keep f i + -- parent inlines would prevent links from being correctly + -- parsed, in this case we prioritise the content over the + -- style + (_, Link _ _ _) -> emerge f i + -- always give priority to strong text over emphasis + (Emph _, Strong _) -> emerge f i + -- drop all other nested styles + (_, _) -> collapse f i + + emerge f i = f <> [i] + keep f i = appendToLast f [i] + collapse f i = appendToLast f $ dropInlineParent i + + appendToLast :: [Inline] -> [Inline] -> [Inline] + appendToLast [] toAppend = [setInlineChildren outer toAppend] + appendToLast flattened toAppend + | isOuter lastFlat = init flattened <> [appendTo lastFlat toAppend] + | otherwise = flattened <> [setInlineChildren outer toAppend] + where lastFlat = last flattened + appendTo o i = mapNested (<> i) o + isOuter i = emptyParent i == emptyParent outer + emptyParent i = setInlineChildren i [] + +mapNested :: ([Inline] -> [Inline]) -> Inline -> Inline +mapNested f i = setInlineChildren i (f (dropInlineParent i)) + +dropInlineParent :: Inline -> [Inline] +dropInlineParent (Link _ i _) = i +dropInlineParent (Emph i) = i +dropInlineParent (Strong i) = i +dropInlineParent (Strikeout i) = i +dropInlineParent (Superscript i) = i +dropInlineParent (Subscript i) = i +dropInlineParent (SmallCaps i) = i +dropInlineParent (Cite _ i) = i +dropInlineParent (Image _ i _) = i +dropInlineParent (Span _ i) = i +dropInlineParent (Quoted _ i) = i +dropInlineParent i = [i] -- not a parent, like Str or Space + +setInlineChildren :: Inline -> [Inline] -> Inline +setInlineChildren (Link a _ t) i = Link a i t +setInlineChildren (Emph _) i = Emph i +setInlineChildren (Strong _) i = Strong i +setInlineChildren (Strikeout _) i = Strikeout i +setInlineChildren (Superscript _) i = Superscript i +setInlineChildren (Subscript _) i = Subscript i +setInlineChildren (SmallCaps _) i = SmallCaps i +setInlineChildren (Quoted q _) i = Quoted q i +setInlineChildren (Cite c _) i = Cite c i +setInlineChildren (Image a _ t) i = Image a i t +setInlineChildren (Span a _) i = Span a i +setInlineChildren leaf _ = leaf + inlineListToRST :: PandocMonad m => [Inline] -> RST m Doc inlineListToRST = writeInlines . walk transformInlines diff --git a/test/Tests/Writers/RST.hs b/test/Tests/Writers/RST.hs index 29c9328f6..89ad1de48 100644 --- a/test/Tests/Writers/RST.hs +++ b/test/Tests/Writers/RST.hs @@ -4,10 +4,12 @@ module Tests.Writers.RST (tests) where import Prelude import Test.Tasty +import Test.Tasty.HUnit import Tests.Helpers import Text.Pandoc import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder +import Text.Pandoc.Writers.RST infix 4 =: (=:) :: (ToString a, ToPandoc a) @@ -52,6 +54,17 @@ tests = [ testGroup "rubrics" , "" , " quoted"] ] + , testGroup "flatten" + [ testCase "emerges nested styles as expected" $ + flatten (Emph [Str "1", Strong [Str "2"], Str "3"]) @?= + [Emph [Str "1"], Strong [Str "2"], Emph [Str "3"]] + , testCase "could introduce trailing spaces" $ + flatten (Emph [Str "f", Space, Strong [Str "2"]]) @?= + [Emph [Str "f", Space], Strong [Str "2"]] + -- the test above is the reason why we call + -- stripLeadingTrailingSpace through transformNested after + -- flatten + ] , testGroup "inlines" [ "are removed when empty" =: -- #4434 plain (strong (str "")) =?> "" @@ -64,6 +77,17 @@ tests = [ testGroup "rubrics" strong (space <> str "text" <> space <> space) =?> "**text**" , "single space stripped" =: strong space =?> "" + , "give priority to strong style over emphasis" =: + strong (emph (strong (str "s"))) =?> "**s**" + , "links are not elided by outer style" =: + strong (emph (link "loc" "" (str "text"))) =?> + "`text `__" + , "RST inlines cannot start nor end with spaces" =: + emph (str "f" <> space <> strong (str "d") <> space <> str "l") =?> + "*f*\\ **d**\\ *l*" + , "keeps quotes" =: + strong (str "f" <> doubleQuoted (str "d") <> str "l") =?> + "**f“d”l**" ] , testGroup "headings" [ "normal heading" =: diff --git a/test/writer.rst b/test/writer.rst index 3353d11d3..0c986b887 100644 --- a/test/writer.rst +++ b/test/writer.rst @@ -615,21 +615,21 @@ This is *emphasized*, and so *is this*. This is **strong**, and so **is this**. -An *`emphasized link `__*. +An `emphasized link `__. -***This is strong and em.*** +**This is strong and em.** -So is ***this*** word. +So is **this** word. -***This is strong and em.*** +**This is strong and em.** -So is ***this*** word. +So is **this** word. This is code: ``>``, ``$``, ``\``, ``\$``, ````. -[STRIKEOUT:This is *strikeout*.] +[STRIKEOUT:This is strikeout.] -Superscripts: a\ :sup:`bc`\ d a\ :sup:`*hello*` a\ :sup:`hello there`. +Superscripts: a\ :sup:`bc`\ d a\ :sup:`hello` a\ :sup:`hello there`. Subscripts: H\ :sub:`2`\ O, H\ :sub:`23`\ O, H\ :sub:`many of them`\ O. -- cgit v1.2.3 From 3ed4861c6290ab51cc45ba585237b33d96a0c03c Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 26 Apr 2018 09:40:27 -0700 Subject: Make `--ascii` work with `ms` and `man` output. --- src/Text/Pandoc/App.hs | 24 ++++++++++++++++-------- 1 file changed, 16 insertions(+), 8 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index e9778fffc..b5683ca87 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -52,7 +52,7 @@ import Data.Aeson (defaultOptions) import Data.Aeson.TH (deriveJSON) import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as B -import Data.Char (toLower, toUpper) +import Data.Char (toLower, toUpper, isAscii, ord) import Data.List (find, intercalate, isPrefixOf, isSuffixOf, sort) import qualified Data.Map as M import Data.Maybe (fromMaybe, isJust, isNothing) @@ -513,16 +513,18 @@ convertWithOpts opts = do let htmlFormat = format `elem` ["html","html4","html5","s5","slidy", "slideous","dzslides","revealjs"] - handleEntities = if (htmlFormat || - format == "docbook4" || - format == "docbook5" || - format == "docbook") && optAscii opts - then toEntities - else id + escape + | optAscii opts + , htmlFormat || format == "docbook4" || + format == "docbook5" || format == "docbook" = + toEntities + | optAscii opts + , format == "ms" || format == "man" = groffEscape + | otherwise = id addNl = if standalone then id else (<> T.singleton '\n') - output <- (addNl . handleEntities) <$> f writerOptions doc + output <- (addNl . escape) <$> f writerOptions doc writerFn eol outputFile =<< if optSelfContained opts && htmlFormat -- TODO not maximally efficient; change type @@ -530,6 +532,12 @@ convertWithOpts opts = do then T.pack <$> makeSelfContained (T.unpack output) else return output +groffEscape :: Text -> Text +groffEscape = T.concatMap toUchar + where toUchar c + | isAscii c = T.singleton c + | otherwise = T.pack $ printf "\\[u%04X]" (ord c) + type Transform = Pandoc -> Pandoc isTextFormat :: String -> Bool -- cgit v1.2.3 From e3d05171f3661008a3377c2b0f793fc846cfe497 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 26 Apr 2018 09:44:31 -0700 Subject: Make `--ascii` work for all XML formats (ICML, OPML, JATS,...). Also document in manual. --- MANUAL.txt | 7 ++++--- src/Text/Pandoc/App.hs | 5 +++-- 2 files changed, 7 insertions(+), 5 deletions(-) (limited to 'src') diff --git a/MANUAL.txt b/MANUAL.txt index 938bacf20..a68e8efbf 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -830,9 +830,10 @@ Options affecting specific writers `--ascii` -: Use only ASCII characters in output. Currently supported only for - HTML and DocBook output (which uses numerical entities instead of - UTF-8 when this option is selected). +: Use only ASCII characters in output. Currently supported for + XML and HTML formats (which use numerical entities instead of + UTF-8 when this option is selected) and for groff ms and man + (which use hexadecimal escapes). `--reference-links` diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index b5683ca87..99277d434 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -516,8 +516,9 @@ convertWithOpts opts = do escape | optAscii opts , htmlFormat || format == "docbook4" || - format == "docbook5" || format == "docbook" = - toEntities + format == "docbook5" || format == "docbook" || + format == "jats" || format == "opml" || + format == "icml" = toEntities | optAscii opts , format == "ms" || format == "man" = groffEscape | otherwise = id -- cgit v1.2.3 From a96c762a10f9b6e97a5660664750ad6e3ef7f5b7 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 26 Apr 2018 12:10:39 -0700 Subject: RST reader: fix anonymous redirects with backticks. Closes #4598. --- src/Text/Pandoc/Readers/RST.hs | 11 ++++++++--- test/command/4598.md | 10 ++++++++++ 2 files changed, 18 insertions(+), 3 deletions(-) create mode 100644 test/command/4598.md (limited to 'src') diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index 1577908a3..71a38cf82 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -1090,10 +1090,15 @@ targetURI :: Monad m => ParserT [Char] st m [Char] targetURI = do skipSpaces optional newline - contents <- many1 (try (many spaceChar >> newline >> - many1 spaceChar >> noneOf " \t\n") <|> noneOf "\n") + contents <- trim <$> + many1 (satisfy (/='\n') + <|> try (newline >> many1 spaceChar >> noneOf " \t\n")) blanklines - return $ escapeURI $ trim contents + case reverse contents of + -- strip backticks + '_':'`':xs -> return (dropWhile (=='`') (reverse xs) ++ "_") + '_':_ -> return contents + _ -> return (escapeURI contents) substKey :: PandocMonad m => RSTParser m () substKey = try $ do diff --git a/test/command/4598.md b/test/command/4598.md new file mode 100644 index 000000000..fedfe888a --- /dev/null +++ b/test/command/4598.md @@ -0,0 +1,10 @@ +``` +% pandoc -f rst +`x`__ + +__ `xy`_ + +.. _`xy`: http://xy.org +^D +

x

+``` -- cgit v1.2.3 From 1927bc9aac0e822bd6179323e00fe38bee5a2cf3 Mon Sep 17 00:00:00 2001 From: Alexander Date: Thu, 26 Apr 2018 22:33:18 +0300 Subject: Add FB2 reader (#4539) --- pandoc.cabal | 4 + src/Text/Pandoc/App.hs | 1 + src/Text/Pandoc/Readers.hs | 3 + src/Text/Pandoc/Readers/FB2.hs | 402 ++++++++++++++++++++++++++++++++++++++++ test/Tests/Readers/FB2.hs | 29 +++ test/fb2/reader/emphasis.fb2 | 11 ++ test/fb2/reader/emphasis.native | 6 + test/fb2/reader/epigraph.fb2 | 18 ++ test/fb2/reader/epigraph.native | 9 + test/fb2/reader/meta.fb2 | 26 +++ test/fb2/reader/meta.native | 2 + test/fb2/reader/poem.fb2 | 28 +++ test/fb2/reader/poem.native | 14 ++ test/fb2/reader/titles.fb2 | 18 ++ test/fb2/reader/titles.native | 8 + test/test-pandoc.hs | 2 + 16 files changed, 581 insertions(+) create mode 100644 src/Text/Pandoc/Readers/FB2.hs create mode 100644 test/Tests/Readers/FB2.hs create mode 100644 test/fb2/reader/emphasis.fb2 create mode 100644 test/fb2/reader/emphasis.native create mode 100644 test/fb2/reader/epigraph.fb2 create mode 100644 test/fb2/reader/epigraph.native create mode 100644 test/fb2/reader/meta.fb2 create mode 100644 test/fb2/reader/meta.native create mode 100644 test/fb2/reader/poem.fb2 create mode 100644 test/fb2/reader/poem.native create mode 100644 test/fb2/reader/titles.fb2 create mode 100644 test/fb2/reader/titles.native (limited to 'src') diff --git a/pandoc.cabal b/pandoc.cabal index 24fba87f7..383a35931 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -301,6 +301,8 @@ extra-source-files: test/fb2/images-embedded.html test/fb2/images-embedded.fb2 test/fb2/test-small.png + test/fb2/reader/*.fb2 + test/fb2/reader/*.native test/fb2/test.jpg test/docx/*.docx test/docx/golden/*.docx @@ -445,6 +447,7 @@ library Text.Pandoc.Readers.Odt, Text.Pandoc.Readers.EPUB, Text.Pandoc.Readers.Muse, + Text.Pandoc.Readers.FB2, Text.Pandoc.Writers, Text.Pandoc.Writers.Native, Text.Pandoc.Writers.Docbook, @@ -663,6 +666,7 @@ test-suite test-pandoc Tests.Readers.EPUB Tests.Readers.Muse Tests.Readers.Creole + Tests.Readers.FB2 Tests.Writers.Native Tests.Writers.ConTeXt Tests.Writers.Docbook diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 99277d434..9a3e00c9f 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -738,6 +738,7 @@ defaultReaderName fallback (x:xs) = ".odt" -> "odt" ".pdf" -> "pdf" -- so we get an "unknown reader" error ".doc" -> "doc" -- so we get an "unknown reader" error + ".fb2" -> "fb2" _ -> defaultReaderName fallback xs -- Determine default writer based on output file extension diff --git a/src/Text/Pandoc/Readers.hs b/src/Text/Pandoc/Readers.hs index 680e7e0b0..7b7f92b35 100644 --- a/src/Text/Pandoc/Readers.hs +++ b/src/Text/Pandoc/Readers.hs @@ -65,6 +65,7 @@ module Text.Pandoc.Readers , readTxt2Tags , readEPUB , readMuse + , readFB2 -- * Miscellaneous , getReader , getDefaultExtensions @@ -86,6 +87,7 @@ import Text.Pandoc.Readers.Creole import Text.Pandoc.Readers.DocBook import Text.Pandoc.Readers.Docx import Text.Pandoc.Readers.EPUB +import Text.Pandoc.Readers.FB2 import Text.Pandoc.Readers.Haddock import Text.Pandoc.Readers.HTML (readHtml) import Text.Pandoc.Readers.JATS (readJATS) @@ -143,6 +145,7 @@ readers = [ ("native" , TextReader readNative) ,("t2t" , TextReader readTxt2Tags) ,("epub" , ByteStringReader readEPUB) ,("muse" , TextReader readMuse) + ,("fb2" , TextReader readFB2) ] -- | Retrieve reader, extensions based on formatSpec (format+extensions). diff --git a/src/Text/Pandoc/Readers/FB2.hs b/src/Text/Pandoc/Readers/FB2.hs new file mode 100644 index 000000000..99b71922f --- /dev/null +++ b/src/Text/Pandoc/Readers/FB2.hs @@ -0,0 +1,402 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE TupleSections #-} +{- +Copyright (C) 2018 Alexander Krotov + +This program is free software; you can redistribute it and/or modify +it under the terms of the GNU General Public License as published by +the Free Software Foundation; either version 2 of the License, or +(at your option) any later version. + +This program is distributed in the hope that it will be useful, +but WITHOUT ANY WARRANTY; without even the implied warranty of +MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +GNU General Public License for more details. + +You should have received a copy of the GNU General Public License +along with this program; if not, write to the Free Software +Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA +-} + +{- | + Module : Text.Pandoc.Readers.FB2 + Copyright : Copyright (C) 2018 Alexander Krotov + License : GNU GPL, version 2 or above + + Maintainer : Alexander Krotov + Stability : alpha + Portability : portable + +Conversion of FB2 to 'Pandoc' document. +-} + +{- + +TODO: + - Tables + - Named styles + - Parse ID attribute for all elements that have it + +-} + +module Text.Pandoc.Readers.FB2 ( readFB2 ) where +import Prelude +import Control.Monad.Except (throwError) +import Control.Monad.State.Strict +import Data.ByteString.Lazy.Char8 ( pack ) +import Data.ByteString.Base64.Lazy +import Data.Char (isSpace, toUpper) +import Data.List (dropWhileEnd, intersperse) +import Data.List.Split (splitOn) +import Data.Text (Text) +import Data.Default +import Data.Maybe +import Text.HTML.TagSoup.Entity (lookupEntity) +import Text.Pandoc.Builder +import Text.Pandoc.Class (PandocMonad, insertMedia) +import Text.Pandoc.Error +import Text.Pandoc.Options +import Text.Pandoc.Shared (crFilter) +import Text.XML.Light + +type FB2 m = StateT FB2State m + +data FB2State = FB2State{ fb2SectionLevel :: Int + , fb2Meta :: Meta + , fb2Authors :: [String] + } deriving Show + +instance Default FB2State where + def = FB2State{ fb2SectionLevel = 1 + , fb2Meta = mempty + , fb2Authors = [] + } + +instance HasMeta FB2State where + setMeta field v s = s {fb2Meta = setMeta field v (fb2Meta s)} + deleteMeta field s = s {fb2Meta = deleteMeta field (fb2Meta s)} + +readFB2 :: PandocMonad m => ReaderOptions -> Text -> m Pandoc +readFB2 _ inp = do + (bs, st) <- runStateT (mapM parseBlock $ parseXML (crFilter inp)) def + let authors = if null $ fb2Authors st + then id + else setMeta "author" (map text $ reverse $ fb2Authors st) + pure $ Pandoc (authors $ fb2Meta st) (toList . mconcat $ bs) + +-- * Utility functions + +trim :: String -> String +trim = dropWhileEnd isSpace . dropWhile isSpace + +removeHash :: String -> String +removeHash ('#':xs) = xs +removeHash xs = xs + +convertEntity :: String -> String +convertEntity e = fromMaybe (map toUpper e) (lookupEntity e) + +parseInline :: PandocMonad m => Content -> FB2 m Inlines +parseInline (Elem e) = + case qName $ elName e of + "strong" -> strong <$> parseStyleType e + "emphasis" -> emph <$> parseStyleType e + "style" -> parseNamedStyle e + "a" -> parseLinkType e + "strikethrough" -> strikeout <$> parseStyleType e + "sub" -> subscript <$> parseStyleType e + "sup" -> superscript <$> parseStyleType e + "code" -> pure $ code $ strContent e + "image" -> parseInlineImageElement e + name -> throwError $ PandocParseError ("Couldn't parse FB2 file: unexpected element " ++ name ++ ".") +parseInline (Text x) = pure $ text $ cdData x +parseInline (CRef r) = pure $ str $ convertEntity r + +parseSubtitle :: PandocMonad m => Element -> FB2 m Blocks +parseSubtitle e = headerWith ("", ["unnumbered"], []) <$> gets fb2SectionLevel <*> parsePType e + +-- * Root element parser + +parseBlock :: PandocMonad m => Content -> FB2 m Blocks +parseBlock (Elem e) = + case qName $ elName e of + "?xml" -> pure mempty + "FictionBook" -> mconcat <$> mapM parseFictionBookChild (elChildren e) + name -> throwError $ PandocParseError ("Couldn't parse FB2 file: unexpected element " ++ name ++ ".") +parseBlock _ = pure mempty + +-- | Parse a child of @\@ element. +parseFictionBookChild :: PandocMonad m => Element -> FB2 m Blocks +parseFictionBookChild e = + case qName $ elName e of + "stylesheet" -> pure mempty -- stylesheet is ignored + "description" -> mempty <$ mapM_ parseDescriptionChild (elChildren e) + "body" -> mconcat <$> mapM parseBodyChild (elChildren e) + "binary" -> mempty <$ parseBinaryElement e + name -> throwError $ PandocParseError ("Couldn't parse FB2 file: unexpected element " ++ name ++ "in FictionBook.") + +-- | Parse a child of @\@ element. +parseDescriptionChild :: PandocMonad m => Element -> FB2 m () +parseDescriptionChild e = + case qName $ elName e of + "title-info" -> mapM_ parseTitleInfoChild (elChildren e) + "src-title-info" -> pure () -- ignore + "document-info" -> pure () + "publish-info" -> pure () + "custom-info" -> pure () + "output" -> pure () + name -> throwError $ PandocParseError ("Couldn't parse FB2 file: unexpected element " ++ name ++ "in description.") + +-- | Parse a child of @\@ element. +parseBodyChild :: PandocMonad m => Element -> FB2 m Blocks +parseBodyChild e = + case qName $ elName e of + "image" -> parseImageElement e + "title" -> header <$> gets fb2SectionLevel <*> parseTitleType (elContent e) + "epigraph" -> parseEpigraph e + "section" -> parseSection e + name -> throwError $ PandocParseError ("Couldn't parse FB2 file: unexpected element " ++ name ++ " in body.") + +-- | Parse a @\@ element. +parseBinaryElement :: PandocMonad m => Element -> FB2 m () +parseBinaryElement e = + case (findAttr (QName "id" Nothing Nothing) e, findAttr (QName "content-type" Nothing Nothing) e) of + (Nothing, _) -> throwError $ PandocParseError " element must have an \"id\" attribute" + (Just _, Nothing) -> throwError $ PandocParseError " element must have a \"content-type\" attribute" + (Just filename, contentType) -> insertMedia filename contentType (decodeLenient (pack (strContent e))) + +-- * Type parsers + +-- | Parse @authorType@ +parseAuthor :: PandocMonad m => Element -> FB2 m String +parseAuthor e = unwords <$> mapM parseAuthorChild (elChildren e) + +parseAuthorChild :: PandocMonad m => Element -> FB2 m String +parseAuthorChild e = + case qName $ elName e of + "first-name" -> pure $ strContent e + "middle-name" -> pure $ strContent e + "last-name" -> pure $ strContent e + "nickname" -> pure $ strContent e + "home-page" -> pure $ strContent e + "email" -> pure $ strContent e + name -> throwError $ PandocParseError ("Couldn't parse FB2 file: unexpected element " ++ name ++ " in author.") + +-- | Parse @titleType@ +parseTitle :: PandocMonad m => Element -> FB2 m Blocks +parseTitle e = header <$> gets fb2SectionLevel <*> parseTitleType (elContent e) + +parseTitleType :: PandocMonad m => [Content] -> FB2 m Inlines +parseTitleType c = mconcat . intersperse linebreak . catMaybes <$> mapM parseTitleContent c + +parseTitleContent :: PandocMonad m => Content -> FB2 m (Maybe Inlines) +parseTitleContent (Elem e) = + case qName $ elName e of + "p" -> Just <$> parsePType e + "empty-line" -> pure $ Just mempty + _ -> pure mempty +parseTitleContent _ = pure Nothing + +-- | Parse @imageType@ +parseImageElement :: PandocMonad m => Element -> FB2 m Blocks +parseImageElement e = + case href of + Just src -> pure $ para $ imageWith (imgId, [], []) (removeHash src) title alt + Nothing -> throwError $ PandocParseError "Couldn't parse FB2 file: image without href." + where alt = maybe mempty str $ findAttr (QName "alt" Nothing Nothing) e + title = fromMaybe "" $ findAttr (QName "title" Nothing Nothing) e + imgId = fromMaybe "" $ findAttr (QName "id" Nothing Nothing) e + href = findAttr (QName "href" (Just "http://www.w3.org/1999/xlink") Nothing) e + +-- | Parse @pType@ +parsePType :: PandocMonad m => Element -> FB2 m Inlines +parsePType = parseStyleType -- TODO add support for optional "id" and "style" attributes + +-- | Parse @citeType@ +parseCite :: PandocMonad m => Element -> FB2 m Blocks +parseCite e = blockQuote . mconcat <$> mapM parseCiteChild (elChildren e) + +-- | Parse @citeType@ child +parseCiteChild :: PandocMonad m => Element -> FB2 m Blocks +parseCiteChild e = + case qName $ elName e of + "p" -> para <$> parsePType e + "poem" -> parsePoem e + "empty-line" -> pure horizontalRule + "subtitle" -> parseSubtitle e + "table" -> parseTable e + "text-author" -> para <$> parsePType e + name -> throwError $ PandocParseError ("Couldn't parse FB2 file: unexpected element " ++ name ++ " in cite.") + +-- | Parse @poemType@ +parsePoem :: PandocMonad m => Element -> FB2 m Blocks +parsePoem e = mconcat <$> mapM parsePoemChild (elChildren e) + +parsePoemChild :: PandocMonad m => Element -> FB2 m Blocks +parsePoemChild e = + case qName $ elName e of + "title" -> parseTitle e + "subtitle" -> parseSubtitle e + "epigraph" -> parseEpigraph e + "stanza" -> parseStanza e + "text-author" -> para <$> parsePType e + "date" -> pure $ para $ text $ strContent e + name -> throwError $ PandocParseError ("Couldn't parse FB2 file: unexpected element " ++ name ++ " in poem.") + +parseStanza :: PandocMonad m => Element -> FB2 m Blocks +parseStanza e = fromList . joinLineBlocks . toList . mconcat <$> mapM parseStanzaChild (elChildren e) + +joinLineBlocks :: [Block] -> [Block] +joinLineBlocks (LineBlock xs:LineBlock ys:zs) = joinLineBlocks (LineBlock (xs ++ ys) : zs) +joinLineBlocks (x:xs) = x:joinLineBlocks xs +joinLineBlocks [] = [] + +parseStanzaChild :: PandocMonad m => Element -> FB2 m Blocks +parseStanzaChild e = + case qName $ elName e of + "title" -> parseTitle e + "subtitle" -> parseSubtitle e + "v" -> lineBlock . (:[]) <$> parsePType e + name -> throwError $ PandocParseError ("Couldn't parse FB2 file: unexpected element " ++ name ++ " in stanza.") + +-- | Parse @epigraphType@ +parseEpigraph :: PandocMonad m => Element -> FB2 m Blocks +parseEpigraph e = + divWith (divId, ["epigraph"], []) . mconcat <$> mapM parseEpigraphChild (elChildren e) + where divId = fromMaybe "" $ findAttr (QName "id" Nothing Nothing) e + +parseEpigraphChild :: PandocMonad m => Element -> FB2 m Blocks +parseEpigraphChild e = + case qName $ elName e of + "p" -> para <$> parsePType e + "poem" -> parsePoem e + "cite" -> parseCite e + "empty-line" -> pure horizontalRule + "text-author" -> para <$> parsePType e + name -> throwError $ PandocParseError ("Couldn't parse FB2 file: unexpected element " ++ name ++ " in epigraph.") + +-- | Parse @annotationType@ +parseAnnotation :: PandocMonad m => Element -> FB2 m Blocks +parseAnnotation e = mconcat <$> mapM parseAnnotationChild (elChildren e) + +parseAnnotationChild :: PandocMonad m => Element -> FB2 m Blocks +parseAnnotationChild e = + case qName $ elName e of + "p" -> para <$> parsePType e + "poem" -> parsePoem e + "cite" -> parseCite e + "subtitle" -> parseSubtitle e + "table" -> parseTable e + "empty-line" -> pure horizontalRule + name -> throwError $ PandocParseError ("Couldn't parse FB2 file: unexpected element " ++ name ++ " in annotation.") + +-- | Parse @sectionType@ +parseSection :: PandocMonad m => Element -> FB2 m Blocks +parseSection e = do + n <- gets fb2SectionLevel + modify $ \st -> st{ fb2SectionLevel = n + 1 } + let sectionId = fromMaybe "" $ findAttr (QName "id" Nothing Nothing) e + bs <- divWith (sectionId, ["section"], []) . mconcat <$> mapM parseSectionChild (elChildren e) + modify $ \st -> st{ fb2SectionLevel = n } + pure bs + +parseSectionChild :: PandocMonad m => Element -> FB2 m Blocks +parseSectionChild e = + case qName $ elName e of + "title" -> parseBodyChild e + "epigraph" -> parseEpigraph e + "image" -> parseImageElement e + "annotation" -> parseAnnotation e + "poem" -> parsePoem e + "cite" -> parseCite e + "empty-line" -> pure horizontalRule + "table" -> parseTable e + "subtitle" -> parseSubtitle e + "p" -> para <$> parsePType e + "section" -> parseSection e + name -> throwError $ PandocParseError ("Couldn't parse FB2 file: unexpected element " ++ name ++ " in section.") + +-- | parse @styleType@ +parseStyleType :: PandocMonad m => Element -> FB2 m Inlines +parseStyleType e = mconcat <$> mapM parseInline (elContent e) + +-- | Parse @namedStyleType@ +parseNamedStyle :: PandocMonad m => Element -> FB2 m Inlines +parseNamedStyle e = do + content <- mconcat <$> mapM parseNamedStyleChild (elContent e) + let lang = maybeToList $ ("lang",) <$> findAttr (QName "lang" Nothing (Just "xml")) e + case findAttr (QName "name" Nothing Nothing) e of + Just name -> pure $ spanWith ("", [name], lang) content + Nothing -> throwError $ PandocParseError "Couldn't parse FB2 file: link without required name." + +parseNamedStyleChild :: PandocMonad m => Content -> FB2 m Inlines +parseNamedStyleChild (Elem e) = + case qName (elName e) of + "strong" -> strong <$> parseStyleType e + "emphasis" -> emph <$> parseStyleType e + "style" -> parseNamedStyle e + "a" -> parseLinkType e + "strikethrough" -> strikeout <$> parseStyleType e + "sub" -> subscript <$> parseStyleType e + "sup" -> superscript <$> parseStyleType e + "code" -> pure $ code $ strContent e + "image" -> parseInlineImageElement e + name -> throwError $ PandocParseError ("Couldn't parse FB2 file: unexpected element " ++ name ++ ".") +parseNamedStyleChild x = parseInline x + +-- | Parse @linkType@ +parseLinkType :: PandocMonad m => Element -> FB2 m Inlines +parseLinkType e = do + content <- mconcat <$> mapM parseStyleLinkType (elContent e) + case findAttr (QName "href" (Just "http://www.w3.org/1999/xlink") Nothing) e of + Just href -> pure $ link href "" content + Nothing -> throwError $ PandocParseError "Couldn't parse FB2 file: link without required href." + +-- | Parse @styleLinkType@ +parseStyleLinkType :: PandocMonad m => Content -> FB2 m Inlines +parseStyleLinkType x@(Elem e) = + case qName (elName e) of + "a" -> throwError $ PandocParseError "Couldn't parse FB2 file: links cannot be nested." + _ -> parseInline x +parseStyleLinkType x = parseInline x + +-- | Parse @tableType@ +parseTable :: PandocMonad m => Element -> FB2 m Blocks +parseTable _ = pure mempty -- TODO: tables are not supported yet + +-- | Parse @title-infoType@ +parseTitleInfoChild :: PandocMonad m => Element -> FB2 m () +parseTitleInfoChild e = + case qName (elName e) of + "genre" -> pure () + "author" -> parseAuthor e >>= \author -> modify (\st -> st {fb2Authors = author:fb2Authors st}) + "book-title" -> modify (setMeta "title" (text $ strContent e)) + "annotation" -> parseAnnotation e >>= modify . setMeta "abstract" + "keywords" -> modify (setMeta "keywords" (map (MetaString . trim) $ splitOn "," $ strContent e)) + "date" -> modify (setMeta "date" (text $ strContent e)) + "coverpage" -> parseCoverPage e + "lang" -> pure () + "src-lang" -> pure () + "translator" -> pure () + "sequence" -> pure () + name -> throwError $ PandocParseError ("Couldn't parse FB2 file: unexpected element " ++ name ++ " in title-info.") + +parseCoverPage :: PandocMonad m => Element -> FB2 m () +parseCoverPage e = + case findChild (QName "image" (Just "http://www.gribuser.ru/xml/fictionbook/2.0") Nothing) e of + Just img -> case href of + Just src -> modify (setMeta "cover-image" (MetaString $ removeHash src)) + Nothing -> pure () + where href = findAttr (QName "href" (Just "http://www.w3.org/1999/xlink") Nothing) img + Nothing -> pure () + +-- | Parse @inlineImageType@ element +parseInlineImageElement :: PandocMonad m + => Element + -> FB2 m Inlines +parseInlineImageElement e = + case href of + Just src -> pure $ imageWith ("", [], []) (removeHash src) "" alt + Nothing -> throwError $ PandocParseError "Couldn't parse FB2 file: inline image without href." + where alt = maybe mempty str $ findAttr (QName "alt" Nothing Nothing) e + href = findAttr (QName "href" (Just "http://www.w3.org/1999/xlink") Nothing) e diff --git a/test/Tests/Readers/FB2.hs b/test/Tests/Readers/FB2.hs new file mode 100644 index 000000000..9b2983d57 --- /dev/null +++ b/test/Tests/Readers/FB2.hs @@ -0,0 +1,29 @@ +{-# LANGUAGE NoImplicitPrelude #-} + +module Tests.Readers.FB2 (tests) where + +import Prelude +import Test.Tasty +import Tests.Helpers +import Test.Tasty.Golden (goldenVsString) +import qualified Data.ByteString as BS +import Text.Pandoc +import Text.Pandoc.UTF8 (toText, fromTextLazy) +import Data.Text (Text) +import Data.Text.Lazy (fromStrict) +import System.FilePath (replaceExtension) + +fb2ToNative :: Text -> Text +fb2ToNative = purely (writeNative def{ writerTemplate = Just "" }) . purely (readFB2 def) + +fb2Test :: TestName -> FilePath -> TestTree +fb2Test name path = goldenVsString name native (fromTextLazy . fromStrict . fb2ToNative . toText <$> BS.readFile path) + where native = replaceExtension path ".native" + +tests :: [TestTree] +tests = [ fb2Test "Emphasis" "fb2/reader/emphasis.fb2" + , fb2Test "Titles" "fb2/reader/titles.fb2" + , fb2Test "Epigraph" "fb2/reader/epigraph.fb2" + , fb2Test "Poem" "fb2/reader/poem.fb2" + , fb2Test "Meta" "fb2/reader/meta.fb2" + ] diff --git a/test/fb2/reader/emphasis.fb2 b/test/fb2/reader/emphasis.fb2 new file mode 100644 index 000000000..1a936a9d0 --- /dev/null +++ b/test/fb2/reader/emphasis.fb2 @@ -0,0 +1,11 @@ + + + +
+

Plain, strong, emphasis, strong emphasis, emphasized strong.

+

Strikethrough: deleted

+

Subscript and superscript

+

Some code

+
+ +
diff --git a/test/fb2/reader/emphasis.native b/test/fb2/reader/emphasis.native new file mode 100644 index 000000000..422e7bb15 --- /dev/null +++ b/test/fb2/reader/emphasis.native @@ -0,0 +1,6 @@ +Pandoc (Meta {unMeta = fromList []}) +[Div ("",["section"],[]) + [Para [Str "Plain,",Space,Strong [Str "strong"],Str ",",Space,Emph [Str "emphasis"],Str ",",Space,Strong [Emph [Str "strong",Space,Str "emphasis"]],Str ",",Space,Emph [Strong [Str "emphasized",Space,Str "strong"]],Str "."] + ,Para [Str "Strikethrough:",Space,Strikeout [Str "deleted"]] + ,Para [Subscript [Str "Subscript"],Space,Str "and",Space,Superscript [Str "superscript"]] + ,Para [Str "Some",Space,Code ("",[],[]) "code"]]] diff --git a/test/fb2/reader/epigraph.fb2 b/test/fb2/reader/epigraph.fb2 new file mode 100644 index 000000000..5bb5cd2ef --- /dev/null +++ b/test/fb2/reader/epigraph.fb2 @@ -0,0 +1,18 @@ + + + + +

Body epigraph

+
+
+ +

Section epigraph

+
+
+ +

Subsection epigraph

+
+
+
+ +
diff --git a/test/fb2/reader/epigraph.native b/test/fb2/reader/epigraph.native new file mode 100644 index 000000000..a58a3e05b --- /dev/null +++ b/test/fb2/reader/epigraph.native @@ -0,0 +1,9 @@ +Pandoc (Meta {unMeta = fromList []}) +[Div ("",["epigraph"],[]) + [Para [Str "Body",Space,Str "epigraph"]] +,Div ("",["section"],[]) + [Div ("",["epigraph"],[]) + [Para [Str "Section",Space,Str "epigraph"]] + ,Div ("",["section"],[]) + [Div ("",["epigraph"],[]) + [Para [Str "Subsection",Space,Str "epigraph"]]]]] diff --git a/test/fb2/reader/meta.fb2 b/test/fb2/reader/meta.fb2 new file mode 100644 index 000000000..7e1736d64 --- /dev/null +++ b/test/fb2/reader/meta.fb2 @@ -0,0 +1,26 @@ + + + + + + First + Middle + Last + + + Another + Author + + Book title + +

Book annotation

+

Second paragraph of book annotation

+
+ foo, bar, baz + 2018 +
+
+ + <p>Body title</p> + +
diff --git a/test/fb2/reader/meta.native b/test/fb2/reader/meta.native new file mode 100644 index 000000000..71a8795b6 --- /dev/null +++ b/test/fb2/reader/meta.native @@ -0,0 +1,2 @@ +Pandoc (Meta {unMeta = fromList [("abstract",MetaBlocks [Para [Str "Book",Space,Str "annotation"],Para [Str "Second",Space,Str "paragraph",Space,Str "of",Space,Str "book",Space,Str "annotation"]]),("author",MetaList [MetaInlines [Str "First",Space,Str "Middle",Space,Str "Last"],MetaInlines [Str "Another",Space,Str "Author"]]),("date",MetaInlines [Str "2018"]),("keywords",MetaList [MetaString "foo",MetaString "bar",MetaString "baz"]),("title",MetaInlines [Str "Book",Space,Str "title"])]}) +[Header 1 ("",[],[]) [Str "Body",Space,Str "title"]] diff --git a/test/fb2/reader/poem.fb2 b/test/fb2/reader/poem.fb2 new file mode 100644 index 000000000..fcf4a0c02 --- /dev/null +++ b/test/fb2/reader/poem.fb2 @@ -0,0 +1,28 @@ + + + +
+ + + <p>Poem title</p> + + +

Poem epigraph

+
+ + Subtitle + + <p>First stanza title</p> + + Verse + More verse + + + One more stanza + + Author + April 2018 +
+
+ +
diff --git a/test/fb2/reader/poem.native b/test/fb2/reader/poem.native new file mode 100644 index 000000000..67be6a672 --- /dev/null +++ b/test/fb2/reader/poem.native @@ -0,0 +1,14 @@ +Pandoc (Meta {unMeta = fromList []}) +[Div ("",["section"],[]) + [Header 2 ("",[],[]) [Str "Poem",Space,Str "title"] + ,Div ("",["epigraph"],[]) + [Para [Str "Poem",Space,Str "epigraph"]] + ,Header 2 ("",["unnumbered"],[]) [Str "Subtitle"] + ,Header 2 ("",[],[]) [Str "First",Space,Str "stanza",Space,Str "title"] + ,LineBlock + [[Str "Verse"] + ,[Emph [Str "More"],Space,Str "verse"]] + ,LineBlock + [[Str "One",Space,Str "more",Space,Str "stanza"]] + ,Para [Str "Author"] + ,Para [Str "April",Space,Str "2018"]]] diff --git a/test/fb2/reader/titles.fb2 b/test/fb2/reader/titles.fb2 new file mode 100644 index 000000000..cfe9588d8 --- /dev/null +++ b/test/fb2/reader/titles.fb2 @@ -0,0 +1,18 @@ + + + + <p>Body title</p> +
+ <p>Section title</p> +
+ + <p>Subsection title</p> + <p>with multiple paragraphs</p> + +
+
+ <p>Another subsection title</p> +
+
+ +
diff --git a/test/fb2/reader/titles.native b/test/fb2/reader/titles.native new file mode 100644 index 000000000..a6c34f5ea --- /dev/null +++ b/test/fb2/reader/titles.native @@ -0,0 +1,8 @@ +Pandoc (Meta {unMeta = fromList []}) +[Header 1 ("",[],[]) [Str "Body",Space,Str "title"] +,Div ("",["section"],[]) + [Header 2 ("",[],[]) [Str "Section",Space,Str "title"] + ,Div ("",["section"],[]) + [Header 3 ("",[],[]) [Str "Subsection",Space,Str "title",LineBreak,Str "with",Space,Str "multiple",Space,Str "paragraphs"]] + ,Div ("",["section"],[]) + [Header 3 ("",[],[]) [Str "Another",Space,Str "subsection",Space,Str "title"]]]] diff --git a/test/test-pandoc.hs b/test/test-pandoc.hs index 8613d5dda..b70d2286c 100644 --- a/test/test-pandoc.hs +++ b/test/test-pandoc.hs @@ -12,6 +12,7 @@ import qualified Tests.Old import qualified Tests.Readers.Creole import qualified Tests.Readers.Docx import qualified Tests.Readers.EPUB +import qualified Tests.Readers.FB2 import qualified Tests.Readers.HTML import qualified Tests.Readers.JATS import qualified Tests.Readers.LaTeX @@ -75,6 +76,7 @@ tests = testGroup "pandoc tests" [ Tests.Command.tests , testGroup "EPUB" Tests.Readers.EPUB.tests , testGroup "Muse" Tests.Readers.Muse.tests , testGroup "Creole" Tests.Readers.Creole.tests + , testGroup "FB2" Tests.Readers.FB2.tests ] , testGroup "Lua filters" Tests.Lua.tests ] -- cgit v1.2.3 From 9472811694e931fa9b5e5db1e82d755efdf3a3a3 Mon Sep 17 00:00:00 2001 From: Tim Parenti Date: Thu, 26 Apr 2018 15:41:15 -0400 Subject: LaTeX writer: Update \lstinline delimiters. (#4369) Don't delimit \lstinline with characters that are normally escaped. Follow-up to #4111, #4271. --- src/Text/Pandoc/Writers/LaTeX.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) (limited to 'src') diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index d9868b7cd..2904bec06 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -1036,7 +1036,7 @@ inlineToLaTeX (Code (_,classes,_) str) = do Nothing -> "" inNote <- gets stInNote when inNote $ modify $ \s -> s{ stVerbInNote = True } - let chr = case "!\"&'()*,-./:;?@_" \\ str of + let chr = case "!\"'()*,-./:;?@" \\ str of (c:_) -> c [] -> '!' let str' = escapeStringUsing (backslashEscapes "\\{}%~_&") str -- cgit v1.2.3 From 8b01f03eaa0c73259ed7a6d73c649cac65edcddc Mon Sep 17 00:00:00 2001 From: Francesco Occhipinti Date: Fri, 27 Apr 2018 18:01:20 +0200 Subject: RST writer: preserve empty inline parents in flatten (#4603) --- src/Text/Pandoc/Writers/RST.hs | 7 +++++-- test/Tests/Writers/RST.hs | 3 +++ 2 files changed, 8 insertions(+), 2 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 084615357..f82597c55 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -457,8 +457,11 @@ transformInlines = insertBS . -- them either collapsing them in the outer inline container or -- pulling them out of it flatten :: Inline -> [Inline] -flatten outer = combineAll $ dropInlineParent outer - where combineAll = foldl combine [] +flatten outer + | null contents = [outer] + | otherwise = combineAll contents + where contents = dropInlineParent outer + combineAll = foldl combine [] combine :: [Inline] -> Inline -> [Inline] combine f i = diff --git a/test/Tests/Writers/RST.hs b/test/Tests/Writers/RST.hs index 89ad1de48..a1a4510e0 100644 --- a/test/Tests/Writers/RST.hs +++ b/test/Tests/Writers/RST.hs @@ -64,6 +64,9 @@ tests = [ testGroup "rubrics" -- the test above is the reason why we call -- stripLeadingTrailingSpace through transformNested after -- flatten + , testCase "preserves empty parents" $ + flatten (Image ("",[],[]) [] ("loc","title")) @?= + [Image ("",[],[]) [] ("loc","title")] ] , testGroup "inlines" [ "are removed when empty" =: -- #4434 -- cgit v1.2.3 From 5ce91a7e01ba3d9362d91c838052e33729efd6ec Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Fri, 27 Apr 2018 23:33:41 +0300 Subject: FB2 reader: replace some errors with warnings Now FB2 reader can read writer.fb2, which does not validate (yet). --- src/Text/Pandoc/Logging.hs | 7 +++++++ src/Text/Pandoc/Readers/FB2.hs | 20 +++++++++++--------- 2 files changed, 18 insertions(+), 9 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Logging.hs b/src/Text/Pandoc/Logging.hs index 07ed2e570..e6f4fe956 100644 --- a/src/Text/Pandoc/Logging.hs +++ b/src/Text/Pandoc/Logging.hs @@ -101,6 +101,7 @@ data LogMessage = | Deprecated String String | NoTranslation String | CouldNotLoadTranslations String String + | UnexpectedXmlElement String String deriving (Show, Eq, Data, Ord, Typeable, Generic) instance ToJSON LogMessage where @@ -211,6 +212,9 @@ instance ToJSON LogMessage where CouldNotLoadTranslations lang msg -> ["lang" .= Text.pack lang, "message" .= Text.pack msg] + UnexpectedXmlElement element parent -> + ["element" .= Text.pack element, + "parent" .= Text.pack parent] showPos :: SourcePos -> String @@ -305,6 +309,8 @@ showLogMessage msg = CouldNotLoadTranslations lang m -> "Could not load translations for " ++ lang ++ if null m then "" else '\n' : m + UnexpectedXmlElement element parent -> + "Unexpected XML element " ++ element ++ " in " ++ parent messageVerbosity:: LogMessage -> Verbosity messageVerbosity msg = @@ -342,3 +348,4 @@ messageVerbosity msg = Deprecated{} -> WARNING NoTranslation{} -> WARNING CouldNotLoadTranslations{} -> WARNING + UnexpectedXmlElement {} -> WARNING diff --git a/src/Text/Pandoc/Readers/FB2.hs b/src/Text/Pandoc/Readers/FB2.hs index 99b71922f..577fc85b6 100644 --- a/src/Text/Pandoc/Readers/FB2.hs +++ b/src/Text/Pandoc/Readers/FB2.hs @@ -46,6 +46,7 @@ import Control.Monad.State.Strict import Data.ByteString.Lazy.Char8 ( pack ) import Data.ByteString.Base64.Lazy import Data.Char (isSpace, toUpper) +import Data.Functor import Data.List (dropWhileEnd, intersperse) import Data.List.Split (splitOn) import Data.Text (Text) @@ -53,8 +54,9 @@ import Data.Default import Data.Maybe import Text.HTML.TagSoup.Entity (lookupEntity) import Text.Pandoc.Builder -import Text.Pandoc.Class (PandocMonad, insertMedia) +import Text.Pandoc.Class (PandocMonad, insertMedia, report) import Text.Pandoc.Error +import Text.Pandoc.Logging import Text.Pandoc.Options import Text.Pandoc.Shared (crFilter) import Text.XML.Light @@ -122,7 +124,7 @@ parseBlock (Elem e) = case qName $ elName e of "?xml" -> pure mempty "FictionBook" -> mconcat <$> mapM parseFictionBookChild (elChildren e) - name -> throwError $ PandocParseError ("Couldn't parse FB2 file: unexpected element " ++ name ++ ".") + name -> report (UnexpectedXmlElement name "root") $> mempty parseBlock _ = pure mempty -- | Parse a child of @\@ element. @@ -133,7 +135,7 @@ parseFictionBookChild e = "description" -> mempty <$ mapM_ parseDescriptionChild (elChildren e) "body" -> mconcat <$> mapM parseBodyChild (elChildren e) "binary" -> mempty <$ parseBinaryElement e - name -> throwError $ PandocParseError ("Couldn't parse FB2 file: unexpected element " ++ name ++ "in FictionBook.") + name -> report (UnexpectedXmlElement name "FictionBook") $> mempty -- | Parse a child of @\@ element. parseDescriptionChild :: PandocMonad m => Element -> FB2 m () @@ -226,7 +228,7 @@ parseCiteChild e = "subtitle" -> parseSubtitle e "table" -> parseTable e "text-author" -> para <$> parsePType e - name -> throwError $ PandocParseError ("Couldn't parse FB2 file: unexpected element " ++ name ++ " in cite.") + name -> report (UnexpectedXmlElement name "cite") $> mempty -- | Parse @poemType@ parsePoem :: PandocMonad m => Element -> FB2 m Blocks @@ -241,7 +243,7 @@ parsePoemChild e = "stanza" -> parseStanza e "text-author" -> para <$> parsePType e "date" -> pure $ para $ text $ strContent e - name -> throwError $ PandocParseError ("Couldn't parse FB2 file: unexpected element " ++ name ++ " in poem.") + name -> report (UnexpectedXmlElement name "poem") $> mempty parseStanza :: PandocMonad m => Element -> FB2 m Blocks parseStanza e = fromList . joinLineBlocks . toList . mconcat <$> mapM parseStanzaChild (elChildren e) @@ -257,7 +259,7 @@ parseStanzaChild e = "title" -> parseTitle e "subtitle" -> parseSubtitle e "v" -> lineBlock . (:[]) <$> parsePType e - name -> throwError $ PandocParseError ("Couldn't parse FB2 file: unexpected element " ++ name ++ " in stanza.") + name -> report (UnexpectedXmlElement name "stanza") $> mempty -- | Parse @epigraphType@ parseEpigraph :: PandocMonad m => Element -> FB2 m Blocks @@ -273,7 +275,7 @@ parseEpigraphChild e = "cite" -> parseCite e "empty-line" -> pure horizontalRule "text-author" -> para <$> parsePType e - name -> throwError $ PandocParseError ("Couldn't parse FB2 file: unexpected element " ++ name ++ " in epigraph.") + name -> report (UnexpectedXmlElement name "epigraph") $> mempty -- | Parse @annotationType@ parseAnnotation :: PandocMonad m => Element -> FB2 m Blocks @@ -288,7 +290,7 @@ parseAnnotationChild e = "subtitle" -> parseSubtitle e "table" -> parseTable e "empty-line" -> pure horizontalRule - name -> throwError $ PandocParseError ("Couldn't parse FB2 file: unexpected element " ++ name ++ " in annotation.") + name -> report (UnexpectedXmlElement name "annotation") $> mempty -- | Parse @sectionType@ parseSection :: PandocMonad m => Element -> FB2 m Blocks @@ -314,7 +316,7 @@ parseSectionChild e = "subtitle" -> parseSubtitle e "p" -> para <$> parsePType e "section" -> parseSection e - name -> throwError $ PandocParseError ("Couldn't parse FB2 file: unexpected element " ++ name ++ " in section.") + name -> report (UnexpectedXmlElement name "section") $> mempty -- | parse @styleType@ parseStyleType :: PandocMonad m => Element -> FB2 m Inlines -- cgit v1.2.3 From 3d766b5c442fc9ff198fe2d3978418343e0bd12f Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Mon, 30 Apr 2018 00:54:56 +0300 Subject: Don't lowercase custom writer filename Fixes #4610 --- src/Text/Pandoc/App.hs | 8 +++----- 1 file changed, 3 insertions(+), 5 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 9a3e00c9f..abc732213 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -223,17 +223,16 @@ convertWithOpts opts = do then pdfWriterAndProg (optWriter opts) (optPdfEngine opts) else return (nonPdfWriterName $ optWriter opts, Nothing) - let format = baseWriterName + let format = map toLower $ baseWriterName $ takeFileName writerName -- in case path to lua script -- disabling the custom writer for now (writer, writerExts) <- if ".lua" `isSuffixOf` format - -- note: use non-lowercased version writerName then return (TextWriter (\o d -> writeCustom writerName o d) :: Writer PandocIO, mempty) - else case getWriter writerName of + else case getWriter (map toLower writerName) of Left e -> E.throwIO $ PandocAppError $ if format == "pdf" then e ++ @@ -844,8 +843,7 @@ options = , Option "tw" ["to","write"] (ReqArg - (\arg opt -> return opt { optWriter = - Just (map toLower arg) }) + (\arg opt -> return opt { optWriter = Just arg }) "FORMAT") "" -- cgit v1.2.3 From cf0b1e435b849193720c33d3e78857ccf1837e6d Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 3 May 2018 18:24:46 -0700 Subject: Relicense TikiWiki reader as GPL v2 or above, like rest of pandoc. Author has given permission in an email, 3 May 2018. See #4591. --- COPYRIGHT | 2 +- src/Text/Pandoc/Readers/TikiWiki.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) (limited to 'src') diff --git a/COPYRIGHT b/COPYRIGHT index 5c673bf1a..ca59fa401 100644 --- a/COPYRIGHT +++ b/COPYRIGHT @@ -123,7 +123,7 @@ Released under the GNU General Public License version 2 or later. src/Text/Pandoc/Readers/TikiWiki.hs Copyright (C) 2017 Robin Lee Powell -Released under the GNU General Public License version 2. +Released under the GNU General Public License version 2 or later. ---------------------------------------------------------------------- src/Text/Pandoc/Readers/JATS.hs diff --git a/src/Text/Pandoc/Readers/TikiWiki.hs b/src/Text/Pandoc/Readers/TikiWiki.hs index 9ba47d183..5c7507248 100644 --- a/src/Text/Pandoc/Readers/TikiWiki.hs +++ b/src/Text/Pandoc/Readers/TikiWiki.hs @@ -6,7 +6,7 @@ {- | Module : Text.Pandoc.Readers.TikiWiki Copyright : Copyright (C) 2017 Robin Lee Powell - License : GPLv2 + License : GNU GPL, version 2 or above Maintainer : Robin Lee Powell Stability : alpha -- cgit v1.2.3 From 59f0c1d83bb573341f8ca0bf796ae41c82afd044 Mon Sep 17 00:00:00 2001 From: Francesco Occhipinti Date: Fri, 4 May 2018 19:31:02 +0200 Subject: catch IO errors when writing media files, closes #4559 (#4619) If we do not catch these errors, any malformed entry in a media bag could cause the loss of a whole document output. An example of malformed entry is an entry with an empty file path. --- src/Text/Pandoc/Class.hs | 10 +++++++++- src/Text/Pandoc/Logging.hs | 6 ++++++ 2 files changed, 15 insertions(+), 1 deletion(-) (limited to 'src') diff --git a/src/Text/Pandoc/Class.hs b/src/Text/Pandoc/Class.hs index 3529054e6..911ba98b5 100644 --- a/src/Text/Pandoc/Class.hs +++ b/src/Text/Pandoc/Class.hs @@ -477,6 +477,14 @@ liftIOError f u = do Left e -> throwError $ PandocIOError u e Right r -> return r +-- | Show potential IO errors to the user continuing execution anyway +logIOError :: IO () -> PandocIO () +logIOError f = do + res <- liftIO $ tryIOError f + case res of + Left e -> report $ IgnoredIOError (E.displayException e) + Right _ -> pure () + instance PandocMonad PandocIO where lookupEnv = liftIO . IO.lookupEnv getCurrentTime = liftIO IO.getCurrentTime @@ -862,7 +870,7 @@ writeMedia dir mediabag subpath = do Just (_, bs) -> do report $ Extracting fullpath liftIOError (createDirectoryIfMissing True) (takeDirectory fullpath) - liftIOError (\p -> BL.writeFile p bs) fullpath + logIOError $ BL.writeFile fullpath bs adjustImagePath :: FilePath -> [FilePath] -> Inline -> Inline adjustImagePath dir paths (Image attr lab (src, tit)) diff --git a/src/Text/Pandoc/Logging.hs b/src/Text/Pandoc/Logging.hs index e6f4fe956..4b025821c 100644 --- a/src/Text/Pandoc/Logging.hs +++ b/src/Text/Pandoc/Logging.hs @@ -85,6 +85,7 @@ data LogMessage = | InlineNotRendered Inline | BlockNotRendered Block | DocxParserWarning String + | IgnoredIOError String | CouldNotFetchResource String String | CouldNotDetermineImageSize String String | CouldNotConvertImage String String @@ -175,6 +176,8 @@ instance ToJSON LogMessage where ["contents" .= toJSON bl] DocxParserWarning s -> ["contents" .= Text.pack s] + IgnoredIOError s -> + ["contents" .= Text.pack s] CouldNotFetchResource fp s -> ["path" .= Text.pack fp, "message" .= Text.pack s] @@ -265,6 +268,8 @@ showLogMessage msg = "Not rendering " ++ show bl DocxParserWarning s -> "Docx parser warning: " ++ s + IgnoredIOError s -> + "IO Error (ignored): " ++ s CouldNotFetchResource fp s -> "Could not fetch resource '" ++ fp ++ "'" ++ if null s then "" else ": " ++ s @@ -332,6 +337,7 @@ messageVerbosity msg = InlineNotRendered{} -> INFO BlockNotRendered{} -> INFO DocxParserWarning{} -> INFO + IgnoredIOError{} -> WARNING CouldNotFetchResource{} -> WARNING CouldNotDetermineImageSize{} -> WARNING CouldNotConvertImage{} -> WARNING -- cgit v1.2.3 From 7c0ef683116d0308da91a61b15b5c640b0e81eda Mon Sep 17 00:00:00 2001 From: Mauro Bieg Date: Sat, 5 May 2018 18:31:17 +0200 Subject: Revert piping html to pdf-engine (#4628) * Revert "PDF: Use withTempDir in html2pdf." We're going back to using tmpFile instead of piping * Revert "html2pdf: inject base tag wih current working directory (#4443)" Fixes #4413 --- src/Text/Pandoc/PDF.hs | 96 ++++++++++++++++++++++++-------------------------- 1 file changed, 46 insertions(+), 50 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs index c73ab2dd9..b171d65b0 100644 --- a/src/Text/Pandoc/PDF.hs +++ b/src/Text/Pandoc/PDF.hs @@ -45,26 +45,23 @@ import qualified Data.ByteString.Lazy.Char8 as BC import Data.Maybe (fromMaybe) import Data.Text (Text) import qualified Data.Text as T -import qualified Data.Text.IO as TextIO import System.Directory import System.Environment import System.Exit (ExitCode (..)) import System.FilePath import System.IO (stdout) -import System.IO.Temp (withTempDirectory) +import System.IO.Temp (withTempDirectory, withTempFile) #if MIN_VERSION_base(4,8,3) import System.IO.Error (IOError, isDoesNotExistError) #else import System.IO.Error (isDoesNotExistError) #endif -import Text.HTML.TagSoup -import Text.HTML.TagSoup.Match import Text.Pandoc.Definition import Text.Pandoc.Error (PandocError (PandocPDFProgramNotFoundError)) import Text.Pandoc.MIME (getMimeType) import Text.Pandoc.Options (HTMLMathMethod (..), WriterOptions (..)) import Text.Pandoc.Process (pipeProcess) -import Text.Pandoc.Shared (inDirectory, stringify, withTempDir) +import Text.Pandoc.Shared (inDirectory, stringify) import qualified Text.Pandoc.UTF8 as UTF8 import Text.Pandoc.Walk (walkM) import Text.Pandoc.Writers.Shared (getField, metaToJSON) @@ -365,51 +362,50 @@ html2pdf :: Verbosity -- ^ Verbosity level -> [String] -- ^ Args to program -> Text -- ^ HTML5 source -> IO (Either ByteString ByteString) -html2pdf verbosity program args htmlSource = do - cwd <- getCurrentDirectory - let tags = parseTags htmlSource - (hd, tl) = break (tagClose (== "head")) tags - baseTag = TagOpen "base" - [("href", T.pack cwd <> T.singleton pathSeparator)] : [TagText "\n"] - source = renderTags $ hd ++ baseTag ++ tl - withTempDir "html2pdf.pdf" $ \tmpdir -> do - let pdfFile = tmpdir "out.pdf" - let pdfFileArgName = ["-o" | program == "prince"] - let programArgs = args ++ ["-"] ++ pdfFileArgName ++ [pdfFile] - env' <- getEnvironment - when (verbosity >= INFO) $ do - putStrLn "[makePDF] Command line:" - putStrLn $ program ++ " " ++ unwords (map show programArgs) - putStr "\n" - putStrLn "[makePDF] Environment:" - mapM_ print env' - putStr "\n" - putStrLn "[makePDF] Contents of intermediate HTML:" - TextIO.putStr source - putStr "\n" - (exit, out) <- E.catch - (pipeProcess (Just env') program programArgs $ BL.fromStrict $ UTF8.fromText source) - (\(e :: IOError) -> if isDoesNotExistError e - then E.throwIO $ - PandocPDFProgramNotFoundError program - else E.throwIO e) - when (verbosity >= INFO) $ do - BL.hPutStr stdout out - putStr "\n" - pdfExists <- doesFileExist pdfFile - mbPdf <- if pdfExists - -- We read PDF as a strict bytestring to make sure that the - -- temp directory is removed on Windows. - -- See https://github.com/jgm/pandoc/issues/1192. - then do - res <- (Just . BL.fromChunks . (:[])) `fmap` BS.readFile pdfFile - removeFile pdfFile - return res - else return Nothing - return $ case (exit, mbPdf) of - (ExitFailure _, _) -> Left out - (ExitSuccess, Nothing) -> Left "" - (ExitSuccess, Just pdf) -> Right pdf +html2pdf verbosity program args source = do + -- write HTML to temp file so we don't have to rewrite + -- all links in `a`, `img`, `style`, `script`, etc. tags, + -- and piping to weasyprint didn't work on Windows either. + file <- withTempFile "." "html2pdf.html" $ \fp _ -> return fp + pdfFile <- withTempFile "." "html2pdf.pdf" $ \fp _ -> return fp + BS.writeFile file $ UTF8.fromText source + let pdfFileArgName = ["-o" | program == "prince"] + let programArgs = args ++ [file] ++ pdfFileArgName ++ [pdfFile] + env' <- getEnvironment + when (verbosity >= INFO) $ do + putStrLn "[makePDF] Command line:" + putStrLn $ program ++ " " ++ unwords (map show programArgs) + putStr "\n" + putStrLn "[makePDF] Environment:" + mapM_ print env' + putStr "\n" + putStrLn $ "[makePDF] Contents of " ++ file ++ ":" + BL.readFile file >>= BL.putStr + putStr "\n" + (exit, out) <- E.catch + (pipeProcess (Just env') program programArgs BL.empty) + (\(e :: IOError) -> if isDoesNotExistError e + then E.throwIO $ + PandocPDFProgramNotFoundError program + else E.throwIO e) + removeFile file + when (verbosity >= INFO) $ do + BL.hPutStr stdout out + putStr "\n" + pdfExists <- doesFileExist pdfFile + mbPdf <- if pdfExists + -- We read PDF as a strict bytestring to make sure that the + -- temp directory is removed on Windows. + -- See https://github.com/jgm/pandoc/issues/1192. + then do + res <- (Just . BL.fromChunks . (:[])) `fmap` BS.readFile pdfFile + removeFile pdfFile + return res + else return Nothing + return $ case (exit, mbPdf) of + (ExitFailure _, _) -> Left out + (ExitSuccess, Nothing) -> Left "" + (ExitSuccess, Just pdf) -> Right pdf context2pdf :: Verbosity -- ^ Verbosity level -> FilePath -- ^ temp directory for output -- cgit v1.2.3 From 621e86402339209ea340dd36dfbd3d9eefc28e85 Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Mon, 7 May 2018 14:20:42 +0300 Subject: Use Data.Maybe.fromMaybe --- src/Text/Pandoc/Readers/Org/Meta.hs | 9 +++------ 1 file changed, 3 insertions(+), 6 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Readers/Org/Meta.hs b/src/Text/Pandoc/Readers/Org/Meta.hs index 938e393bb..965e33d94 100644 --- a/src/Text/Pandoc/Readers/Org/Meta.hs +++ b/src/Text/Pandoc/Readers/Org/Meta.hs @@ -50,6 +50,7 @@ import Text.Pandoc.Shared (safeRead) import Control.Monad (mzero, void, when) import Data.Char (toLower) import Data.List (intersperse) +import Data.Maybe (fromMaybe) import qualified Data.Map as M import Network.HTTP (urlEncode) @@ -191,16 +192,12 @@ parseFormat = try $ replacePlain <|> replaceUrl <|> justAppend setEmphasisPreChar :: Maybe [Char] -> OrgParserState -> OrgParserState setEmphasisPreChar csMb st = - let preChars = case csMb of - Nothing -> orgStateEmphasisPreChars defaultOrgParserState - Just cs -> cs + let preChars = fromMaybe (orgStateEmphasisPostChars defaultOrgParserState) csMb in st { orgStateEmphasisPreChars = preChars } setEmphasisPostChar :: Maybe [Char] -> OrgParserState -> OrgParserState setEmphasisPostChar csMb st = - let postChars = case csMb of - Nothing -> orgStateEmphasisPostChars defaultOrgParserState - Just cs -> cs + let postChars = fromMaybe (orgStateEmphasisPostChars defaultOrgParserState) csMb in st { orgStateEmphasisPostChars = postChars } emphChars :: Monad m => OrgParser m (Maybe [Char]) -- cgit v1.2.3 From 58799234227200b480b21a8f6611bdf3b6e2528a Mon Sep 17 00:00:00 2001 From: Alexander Krotov Date: Mon, 7 May 2018 14:54:20 +0300 Subject: Muse writer: add support for left-align and right-align classes Address issue #4542 --- src/Text/Pandoc/Writers/Muse.hs | 10 ++++++++-- test/Tests/Writers/Muse.hs | 6 ++++++ 2 files changed, 14 insertions(+), 2 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 6ed6ed1ca..3681fcc0d 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -511,7 +511,7 @@ inlineToMuse (Link _ txt (src, _)) = isImageUrl = (`elem` imageExtensions) . takeExtension inlineToMuse (Image attr alt (source,'f':'i':'g':':':title)) = inlineToMuse (Image attr alt (source,title)) -inlineToMuse (Image attr inlines (source, title)) = do +inlineToMuse (Image attr@(_, classes, _) inlines (source, title)) = do opts <- asks envOptions alt <- local (\env -> env { envInsideLinkDescription = True }) $ inlineListToMuse inlines let title' = if null title @@ -522,7 +522,13 @@ inlineToMuse (Image attr inlines (source, title)) = do let width = case dimension Width attr of Just (Percent x) | isEnabled Ext_amuse opts -> " " ++ show (round x :: Integer) _ -> "" - return $ "[[" <> text (urlEscapeBrackets source ++ width) <> "]" <> title' <> "]" + let leftalign = if "align-left" `elem` classes + then " l" + else "" + let rightalign = if "align-right" `elem` classes + then " r" + else "" + return $ "[[" <> text (urlEscapeBrackets source ++ width ++ leftalign ++ rightalign) <> "]" <> title' <> "]" inlineToMuse (Note contents) = do -- add to notes in state notes <- gets stNotes diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index ff66d1d65..50c0e78eb 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -425,6 +425,12 @@ tests = [ testGroup "block elements" , "image with width" =: imageWith ("", [], [("width", "60%")]) "image.png" "Image" (str "") =?> "[[image.png 60][Image]]" + , "left-aligned image with width" =: + imageWith ("", ["align-left"], [("width", "60%")]) "image.png" "Image" (str "") =?> + "[[image.png 60 l][Image]]" + , "right-aligned image with width" =: + imageWith ("", ["align-right"], [("width", "60%")]) "image.png" "Image" (str "") =?> + "[[image.png 60 r][Image]]" , "escape brackets in image title" =: image "image.png" "Foo]bar" (str "") =?> "[[image.png][Foo]bar]]" , "note" =: note (plain (text "Foo")) =?> unlines [ "[1]" -- cgit v1.2.3 From 0d83ce3bc4c68efa9d19f065a056d27d9b8ec56d Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Mon, 7 May 2018 17:44:05 -0700 Subject: HTML writer: Strip links from headers when creating TOC. Otherwise the TOC entries will not link to the sections. Closes #4340. --- src/Text/Pandoc/Writers/HTML.hs | 16 ++++++++++++---- 1 file changed, 12 insertions(+), 4 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 762bbd0e5..646168c72 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -354,7 +354,8 @@ defList :: PandocMonad m defList opts items = toList H.dl opts (items ++ [nl opts]) -- | Construct table of contents from list of elements. -tableOfContents :: PandocMonad m => WriterOptions -> [Element] -> StateT WriterState m (Maybe Html) +tableOfContents :: PandocMonad m => WriterOptions -> [Element] + -> StateT WriterState m (Maybe Html) tableOfContents _ [] = return Nothing tableOfContents opts sects = do contents <- mapM (elementToListItem opts) sects @@ -369,7 +370,8 @@ showSecNum = intercalate "." . map show -- | Converts an Element to a list item for a table of contents, -- retrieving the appropriate identifier from state. -elementToListItem :: PandocMonad m => WriterOptions -> Element -> StateT WriterState m (Maybe Html) +elementToListItem :: PandocMonad m => WriterOptions -> Element + -> StateT WriterState m (Maybe Html) -- Don't include the empty headers created in slide shows -- shows when an hrule is used to separate slides without a new title: elementToListItem _ (Sec _ _ _ [Str "\0"] _) = return Nothing @@ -381,7 +383,8 @@ elementToListItem opts (Sec lev num (id',classes,_) headerText subsecs) then (H.span ! A.class_ "toc-section-number" $ toHtml $ showSecNum num') >> preEscapedString " " else mempty - txt <- liftM (sectnum >>) $ inlineListToHtml opts $ walk deNote headerText + txt <- liftM (sectnum >>) $ + inlineListToHtml opts $ walk (deLink . deNote) headerText subHeads <- mapM (elementToListItem opts) subsecs >>= return . catMaybes subList <- if null subHeads then return mempty @@ -397,8 +400,13 @@ elementToListItem opts (Sec lev num (id',classes,_) headerText subsecs) $ toHtml txt) >> subList elementToListItem _ _ = return Nothing +deLink :: Inline -> Inline +deLink (Link _ ils _) = Span nullAttr ils +deLink x = x + -- | Convert an Element to Html. -elementToHtml :: PandocMonad m => Int -> WriterOptions -> Element -> StateT WriterState m Html +elementToHtml :: PandocMonad m => Int -> WriterOptions -> Element + -> StateT WriterState m Html elementToHtml _slideLevel opts (Blk block) = blockToHtml opts block elementToHtml slideLevel opts (Sec level num (id',classes,keyvals) title' elements) = do slideVariant <- gets stSlideVariant -- cgit v1.2.3 From eb733d136577f5968a283f5d09c036a90be55677 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Tue, 8 May 2018 09:11:39 -0700 Subject: LaTeX reader: handle `$` in `/text{..}` inside math. This fixes the main problem in #4576. There is still an issue about `\SI`, but that's a separate issue. --- src/Text/Pandoc/Readers/LaTeX.hs | 29 ++++++++++++++++++++++------- 1 file changed, 22 insertions(+), 7 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index 041b552dc..39dffde76 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -1053,13 +1053,28 @@ dollarsMath :: PandocMonad m => LP m Inlines dollarsMath = do symbol '$' display <- option False (True <$ symbol '$') - contents <- trim . toksToString <$> - many (notFollowedBy (symbol '$') >> anyTok) - if display - then - mathDisplay contents <$ try (symbol '$' >> symbol '$') - <|> (guard (null contents) >> return (mathInline "")) - else mathInline contents <$ symbol '$' + (do contents <- try $ T.unpack <$> pDollarsMath 0 + if display + then (mathDisplay contents <$ symbol '$') + else return $ mathInline contents) + <|> (guard display >> return (mathInline "")) + +-- Int is number of embedded groupings +pDollarsMath :: PandocMonad m => Int -> LP m Text +pDollarsMath n = do + Tok _ toktype t <- anyTok + case toktype of + Symbol | t == "$" + , n == 0 -> return mempty + | t == "\\" -> do + Tok _ _ t' <- anyTok + return (t <> t') + | t == "{" -> (t <>) <$> pDollarsMath (n+1) + | t == "}" -> + if n > 0 + then (t <>) <$> pDollarsMath (n-1) + else mzero + _ -> (t <>) <$> pDollarsMath n -- citations -- cgit v1.2.3 From 3a291dad3534b6936731b54276b185214a1d6298 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Tue, 8 May 2018 09:54:19 -0700 Subject: Shared: add uriPathToPath. This adjusts the path from a file: URI in a way that is sensitive to Windows/Linux differences. Thus, on Windows, `/c:/foo` gets interpreted as `c:/foo`, but on Linux, `/c:/foo` gets interpreted as `/c:/foo`. See #4613. --- src/Text/Pandoc/Shared.hs | 14 ++++++++++++++ 1 file changed, 14 insertions(+) (limited to 'src') diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 8b1af19cd..82ac32980 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -84,6 +84,7 @@ module Text.Pandoc.Shared ( -- * File handling inDirectory, collapseFilePath, + uriPathToPath, filteredFilesFromArchive, -- * URI handling schemes, @@ -635,6 +636,19 @@ collapseFilePath = Posix.joinPath . reverse . foldl go [] . splitDirectories isSingleton _ = Nothing checkPathSeperator = fmap isPathSeparator . isSingleton +-- Convert the path part of a file: URI to a regular path. +-- On windows, @/c:/foo@ should be @c:/foo@. +-- On linux, @/foo@ should be @/foo@. +uriPathToPath :: String -> FilePath +uriPathToPath path = +#ifdef _WINDOWS + case path of + '/':ps -> ps + _ -> p +#else + path +#endif + -- -- File selection from the archive -- -- cgit v1.2.3 From 780bf64d1d441caf98c29f0544c1eefdb81b1cfa Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Tue, 8 May 2018 09:56:17 -0700 Subject: Use uriPathToPath with file: URIs. Closes #4613. Needs testing on Windows. --- src/Text/Pandoc/App.hs | 4 ++-- src/Text/Pandoc/Class.hs | 3 ++- 2 files changed, 4 insertions(+), 3 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index abc732213..920462d48 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -93,7 +93,7 @@ import Text.Pandoc.Highlighting (highlightingStyles) import Text.Pandoc.PDF (makePDF) import Text.Pandoc.SelfContained (makeDataURI, makeSelfContained) import Text.Pandoc.Shared (eastAsianLineBreakFilter, stripEmptyParagraphs, - headerShift, isURI, ordNub, safeRead, tabFilter) + headerShift, isURI, ordNub, safeRead, tabFilter, uriPathToPath) import qualified Text.Pandoc.UTF8 as UTF8 import Text.Pandoc.Writers.Math (defaultKaTeXURL, defaultMathJaxURL) import Text.Pandoc.XML (toEntities) @@ -795,7 +795,7 @@ readSource src = case parseURI src of readURI src | uriScheme u == "file:" -> liftIO $ UTF8.toText <$> - BS.readFile (uriPath u) + BS.readFile (uriPathToPath $ uriPath u) _ -> liftIO $ UTF8.toText <$> BS.readFile src diff --git a/src/Text/Pandoc/Class.hs b/src/Text/Pandoc/Class.hs index 911ba98b5..4ade2dc6d 100644 --- a/src/Text/Pandoc/Class.hs +++ b/src/Text/Pandoc/Class.hs @@ -110,6 +110,7 @@ import qualified Text.Pandoc.UTF8 as UTF8 import qualified System.Directory as Directory import Data.Time (UTCTime) import Text.Pandoc.Logging +import Text.Pandoc.Shared (uriPathToPath) import Text.Parsec (ParsecT, getPosition, sourceLine, sourceName) import qualified Data.Time as IO (getCurrentTime) import Text.Pandoc.MIME (MimeType, getMimeType, extensionFromMimeType) @@ -598,7 +599,7 @@ downloadOrRead s = do -- We don't want to treat C:/ as a scheme: Just u' | length (uriScheme u') > 2 -> openURL (show u') Just u' | uriScheme u' == "file:" -> - readLocalFile $ dropWhile (=='/') (uriPath u') + readLocalFile $ uriPathToPath (uriPath u') _ -> readLocalFile fp -- get from local file system where readLocalFile f = do resourcePath <- getResourcePath -- cgit v1.2.3 From 40603dd4cd80f633239d1f48da3c3c834412b02e Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Tue, 8 May 2018 10:17:51 -0700 Subject: Support underline in docx writer. Updated golden test and confirmed validity of file. Closes #4633. --- src/Text/Pandoc/Writers/Docx.hs | 3 +++ test/docx/golden/inline_formatting.docx | Bin 9737 -> 9747 bytes 2 files changed, 3 insertions(+) (limited to 'src') diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index 9b65e6ec7..1666c0562 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -1111,6 +1111,9 @@ inlineToOpenXML' _ (Str str) = formattedString str inlineToOpenXML' opts Space = inlineToOpenXML opts (Str " ") inlineToOpenXML' opts SoftBreak = inlineToOpenXML opts (Str " ") +inlineToOpenXML' opts (Span (_,["underline"],_) ils) = do + withTextProp (mknode "w:u" [("w:val","single")] ()) $ + inlinesToOpenXML opts ils inlineToOpenXML' _ (Span (ident,["comment-start"],kvs) ils) = do -- prefer the "id" in kvs, since that is the one produced by the docx -- reader. diff --git a/test/docx/golden/inline_formatting.docx b/test/docx/golden/inline_formatting.docx index 367654e53..9e07bd25d 100644 Binary files a/test/docx/golden/inline_formatting.docx and b/test/docx/golden/inline_formatting.docx differ -- cgit v1.2.3 From b8231a8eca63e887247c8070f59b8d9e6cbd669c Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Tue, 8 May 2018 11:31:00 -0700 Subject: Fixed bug in uriPathToPath for Windows. --- src/Text/Pandoc/Shared.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) (limited to 'src') diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 82ac32980..26b01bc90 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -644,7 +644,7 @@ uriPathToPath path = #ifdef _WINDOWS case path of '/':ps -> ps - _ -> p + ps -> ps #else path #endif -- cgit v1.2.3
Centered Header
Centered Header
First
Centered Header
Centered Header
First