aboutsummaryrefslogtreecommitdiff
path: root/test/Tests/Readers
diff options
context:
space:
mode:
Diffstat (limited to 'test/Tests/Readers')
-rw-r--r--test/Tests/Readers/HTML.hs25
-rw-r--r--test/Tests/Readers/Markdown.hs12
-rw-r--r--test/Tests/Readers/Muse.hs85
-rw-r--r--test/Tests/Readers/Org/Block/Header.hs38
-rw-r--r--test/Tests/Readers/Org/Block/List.hs11
-rw-r--r--test/Tests/Readers/Org/Directive.hs23
-rw-r--r--test/Tests/Readers/Org/Inline.hs9
-rw-r--r--test/Tests/Readers/RST.hs16
8 files changed, 207 insertions, 12 deletions
diff --git a/test/Tests/Readers/HTML.hs b/test/Tests/Readers/HTML.hs
index f61f1f497..eedb99029 100644
--- a/test/Tests/Readers/HTML.hs
+++ b/test/Tests/Readers/HTML.hs
@@ -4,11 +4,14 @@ module Tests.Readers.HTML (tests) where
import Prelude
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.Walk (walk)
html :: Text -> Pandoc
html = purely $ readHtml def
@@ -16,6 +19,27 @@ html = purely $ readHtml def
htmlNativeDivs :: Text -> Pandoc
htmlNativeDivs = purely $ readHtml def { readerExtensions = enableExtension Ext_native_divs $ readerExtensions def }
+makeRoundTrip :: Block -> Block
+makeRoundTrip CodeBlock{} = Para [Str "code block was here"]
+makeRoundTrip LineBlock{} = Para [Str "line block was here"]
+makeRoundTrip RawBlock{} = Para [Str "raw block was here"]
+makeRoundTrip x = x
+
+removeRawInlines :: Inline -> Inline
+removeRawInlines RawInline{} = Str "raw inline was here"
+removeRawInlines x = x
+
+roundTrip :: Blocks -> Bool
+roundTrip b = d'' == d'''
+ where d = walk removeRawInlines $
+ walk makeRoundTrip $ Pandoc nullMeta $ toList b
+ d' = rewrite d
+ d'' = rewrite d'
+ d''' = rewrite d''
+ rewrite = html . T.pack . (++ "\n") . T.unpack .
+ purely (writeHtml5String def
+ { writerWrapText = WrapPreserve })
+
tests :: [TestTree]
tests = [ testGroup "base tag"
[ test html "simple" $
@@ -53,4 +77,5 @@ tests = [ testGroup "base tag"
, test htmlNativeDivs "<main> followed by text" $ "<main>main content</main>non-main content" =?>
doc (divWith ("", [], [("role", "main")]) (plain (text "main content")) <> plain (text "non-main content"))
]
+ , testProperty "Round trip" (withMaxSuccess 25 roundTrip)
]
diff --git a/test/Tests/Readers/Markdown.hs b/test/Tests/Readers/Markdown.hs
index e44c7fc19..be89e708e 100644
--- a/test/Tests/Readers/Markdown.hs
+++ b/test/Tests/Readers/Markdown.hs
@@ -39,7 +39,7 @@ testBareLink (inp, ils) =
(unpack inp) (inp, doc $ para ils)
autolink :: String -> Inlines
-autolink = autolinkWith nullAttr
+autolink = autolinkWith ("",["uri"],[])
autolinkWith :: Attr -> String -> Inlines
autolinkWith attr s = linkWith attr s "" (str s)
@@ -72,10 +72,12 @@ bareLinkTests =
, ("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" ""
+ linkWith ("",["uri"],[])
+ "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" ""
+ linkWith ("",["uri"],[])
+ "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")
@@ -199,7 +201,9 @@ tests = [ testGroup "inline code"
]
, testGroup "emoji"
[ test markdownGH "emoji symbols" $
- ":smile: and :+1:" =?> para (text "😄 and 👍")
+ ":smile: and :+1:" =?> para (spanWith ("", ["emoji"], [("data-emoji", "smile")]) "😄" <>
+ space <> str "and" <> space <>
+ spanWith ("", ["emoji"], [("data-emoji", "+1")]) "👍")
]
, "unbalanced brackets" =:
"[[[[[[[[[[[[hi" =?> para (text "[[[[[[[[[[[[hi")
diff --git a/test/Tests/Readers/Muse.hs b/test/Tests/Readers/Muse.hs
index ecdd5fdb0..958a74915 100644
--- a/test/Tests/Readers/Muse.hs
+++ b/test/Tests/Readers/Muse.hs
@@ -39,9 +39,9 @@ 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 :: Blocks -> Bool
roundTrip b = d' == d''
- where d = walk makeRoundTrip $ Pandoc nullMeta [b]
+ where d = walk makeRoundTrip $ Pandoc nullMeta $ toList b
d' = rewrite d
d'' = rewrite d'
rewrite = amuse . T.pack . (++ "\n") . T.unpack .
@@ -62,6 +62,14 @@ tests =
"*Foo bar*" =?>
para (emph . spcSep $ ["Foo", "bar"])
+ -- Emacs Muse allows this
+ , "Newline in the beginning of emphasis" =:
+ "*\nFoo bar*" =?>
+ para (emph ("Foo" <> space <> "bar"))
+ , "Newline in the end of emphasis" =:
+ "*Foo bar\n*" =?>
+ para (emph ("Foo" <> space <> "bar"))
+
, "Comma after closing *" =:
"Foo *bar*, baz" =?>
para ("Foo " <> emph "bar" <> ", baz")
@@ -74,6 +82,10 @@ tests =
"Foo x*bar* baz" =?>
para "Foo x*bar* baz"
+ , "Digit after closing *" =:
+ "Foo *bar*0 baz" =?>
+ para "Foo *bar*0 baz"
+
, "Emphasis tag" =:
"<em>Foo bar</em>" =?>
para (emph . spcSep $ ["Foo", "bar"])
@@ -138,6 +150,10 @@ tests =
"Foo =bar=, baz" =?>
para (text "Foo " <> code "bar" <> text ", baz")
+ , "Not code if followed by digit" =:
+ "Foo =bar=0 baz" =?>
+ para (text "Foo =bar=0 baz")
+
, "One character code" =: "=c=" =?> para (code "c")
, "Three = characters is not a code" =: "===" =?> para "==="
@@ -194,9 +210,27 @@ tests =
, "Image" =:
"[[image.jpg]]" =?>
para (image "image.jpg" "" mempty)
+ , "Closing bracket is not allowed in image filename" =:
+ "[[foo]bar.jpg]]" =?>
+ para (text "[[foo]bar.jpg]]")
, "Image with description" =:
"[[image.jpg][Image]]" =?>
para (image "image.jpg" "" (text "Image"))
+ , "Image with space in filename" =:
+ "[[image name.jpg]]" =?>
+ para (image "image name.jpg" "" mempty)
+ , "Image with width" =:
+ "[[image.jpg 60]]" =?>
+ para (imageWith ("", [], [("width", "60%")]) "image.jpg" mempty mempty)
+ , "At least one space is required between image filename and width" =:
+ "[[image.jpg60]]" =?>
+ para (link "image.jpg60" mempty (str "image.jpg60"))
+ , "Left-aligned image with width" =:
+ "[[image.png 60 l][Image]]" =?>
+ para (imageWith ("", ["align-left"], [("width", "60%")]) "image.png" "" (str "Image"))
+ , "Right-aligned image with width" =:
+ "[[image.png 60 r][Image]]" =?>
+ para (imageWith ("", ["align-right"], [("width", "60%")]) "image.png" "" (str "Image"))
, "Image link" =:
"[[URL:image.jpg]]" =?>
para (link "image.jpg" "" (str "image.jpg"))
@@ -225,8 +259,8 @@ tests =
]
]
- , testGroup "Blocks" $
- [ testProperty "Round trip" roundTrip
+ , testGroup "Blocks"
+ [ testProperty "Round trip" (withMaxSuccess 25 roundTrip)
, "Block elements end paragraphs" =:
T.unlines [ "First paragraph"
, "----"
@@ -385,6 +419,12 @@ tests =
, "</verse>"
] =?>
lineBlock [ "" ]
+ , "Verse tag with verbatim close tag inside" =:
+ T.unlines [ "<verse>"
+ , "<verbatim></verse></verbatim>"
+ , "</verse>"
+ ] =?>
+ lineBlock [ "</verse>" ]
, testGroup "Example"
[ "Braces on separate lines" =:
T.unlines [ "{{{"
@@ -589,6 +629,18 @@ tests =
T.unlines [ "* Foo"
, "bar"
] =?> header 1 "Foo\nbar"
+ , test (purely $ readMuse def { readerExtensions = extensionsFromList [Ext_amuse, Ext_auto_identifiers]})
+ "Auto identifiers"
+ (T.unlines [ "* foo"
+ , "** Foo"
+ , "* bar"
+ , "** foo"
+ , "* foo"
+ ] =?> headerWith ("foo",[],[]) 1 "foo" <>
+ headerWith ("foo-1",[],[]) 2 "Foo" <>
+ headerWith ("bar",[],[]) 1 "bar" <>
+ headerWith ("foo-2",[],[]) 2 "foo" <>
+ headerWith ("foo-3",[],[]) 1 "foo")
]
, testGroup "Directives"
[ "Title" =:
@@ -710,6 +762,13 @@ tests =
, " > Baz"
] =?>
para ("Foo" <> note (para "Bar" <> lineBlock ["Baz"]))
+ , "Footnote ending in self-terminating element and followed by paragraph" =:
+ T.unlines [ "Foo[1]"
+ , ""
+ , "[1] > bar"
+ , "baz"
+ ] =?>
+ para (str "Foo" <> note (lineBlock ["bar"])) <> para (str "baz")
, test emacsMuse "Emacs multiparagraph footnotes"
(T.unlines
[ "First footnote reference[1] and second footnote reference[2]."
@@ -798,6 +857,14 @@ tests =
[plain "Foo", plain "bar", plain "baz"]
[[plain "First", plain "row", plain "here"],
[plain "Second", plain "row", plain "there"]]
+ , "Table caption with +" =:
+ T.unlines
+ [ "Foo | bar"
+ , "|+ Table + caption +|"
+ ] =?>
+ table (text "Table + caption") (replicate 2 (AlignDefault, 0.0))
+ []
+ [[plain "Foo", plain "bar"]]
, "Caption without table" =:
"|+ Foo bar baz +|" =?>
table (text "Foo bar baz") [] [] []
@@ -972,7 +1039,7 @@ tests =
, para "c"
]
]
- , "List continuation afeter nested list" =:
+ , "List continuation after nested list" =:
T.unlines
[ " - - foo"
, ""
@@ -1118,6 +1185,11 @@ tests =
] =?>
bulletList [ lineBlock [ "foo" ] ] <> bulletList [ para "bar" ]
]
+ , "List ending in self-terminating element and followed by paragraph" =:
+ T.unlines [ " - > Foo"
+ , "bar"
+ ] =?>
+ bulletList [lineBlock ["Foo"]] <> para (str "bar")
-- Test that definition list requires a leading space.
-- Emacs Muse does not require a space, we follow Amusewiki here.
, "Not a definition list" =:
@@ -1335,7 +1407,8 @@ tests =
, " <verse>"
, " </quote>"
, " </verse>"
+ , "</quote>"
] =?>
- para "<quote>" <> bulletList [ para "Foo" <> para "</quote>" <> para "bar" <> lineBlock [ "</quote>" ] ]
+ blockQuote (bulletList [ para "Foo" <> para "</quote>" <> para "bar" <> lineBlock [ "</quote>" ] ])
]
]
diff --git a/test/Tests/Readers/Org/Block/Header.hs b/test/Tests/Readers/Org/Block/Header.hs
index 3b0d7dda9..913c830d6 100644
--- a/test/Tests/Readers/Org/Block/Header.hs
+++ b/test/Tests/Readers/Org/Block/Header.hs
@@ -181,4 +181,42 @@ tests =
, " :END:"
] =?>
headerWith ("not-numbered", ["unnumbered"], []) 1 "Not numbered"
+
+ , testGroup "planning information"
+ [ "Planning info is not included in output" =:
+ T.unlines [ "* important"
+ , T.unwords
+ [ "CLOSED: [2018-09-05 Wed 13:58]"
+ , "DEADLINE: <2018-09-17 Mon>"
+ , "SCHEDULED: <2018-09-10 Mon>"
+ ]
+ ] =?>
+ headerWith ("important", [], []) 1 "important"
+
+ , "Properties after planning info are recognized" =:
+ T.unlines [ "* important "
+ , " " <> T.unwords
+ [ "CLOSED: [2018-09-05 Wed 13:58]"
+ , "DEADLINE: <2018-09-17 Mon>"
+ , "SCHEDULED: <2018-09-10 Mon>"
+ ]
+ , " :PROPERTIES:"
+ , " :custom_id: look"
+ , " :END:"
+ ] =?>
+ headerWith ("look", [], []) 1 "important"
+
+ , "Planning info followed by test" =:
+ T.unlines [ "* important "
+ , " " <> T.unwords
+ [ "CLOSED: [2018-09-05 Wed 13:58]"
+ , "DEADLINE: <2018-09-17 Mon>"
+ , "SCHEDULED: <2018-09-10 Mon>"
+ ]
+ , " :PROPERTIES:"
+ , " :custom_id: look"
+ , " :END:"
+ ] =?>
+ headerWith ("look", [], []) 1 "important"
+ ]
]
diff --git a/test/Tests/Readers/Org/Block/List.hs b/test/Tests/Readers/Org/Block/List.hs
index f273b684d..bdab01404 100644
--- a/test/Tests/Readers/Org/Block/List.hs
+++ b/test/Tests/Readers/Org/Block/List.hs
@@ -243,4 +243,15 @@ tests =
mconcat [ para "CLOSED: [2015-10-19 Mon 15:03]"
, bulletList [ plain "Note taken on [2015-10-19 Mon 13:24]" ]
]
+
+ , "Markup after header and list" =:
+ T.unlines [ "* headline"
+ , "- list"
+ , ""
+ , "~variable name~"
+ ] =?>
+ mconcat [ headerWith ("headline", [], []) 1 "headline"
+ , bulletList [ plain "list" ]
+ , para (code "variable name")
+ ]
]
diff --git a/test/Tests/Readers/Org/Directive.hs b/test/Tests/Readers/Org/Directive.hs
index bb9c52e69..87abb714d 100644
--- a/test/Tests/Readers/Org/Directive.hs
+++ b/test/Tests/Readers/Org/Directive.hs
@@ -150,6 +150,29 @@ tests =
, "* Headline :hello:world:"
] =?>
headerWith ("headline", [], mempty) 1 "Headline"
+
+ , testGroup "planning information"
+ [ "include planning info after headlines" =:
+ T.unlines [ "#+OPTIONS: p:t"
+ , "* important"
+ , " DEADLINE: <2018-10-01 Mon> SCHEDULED: <2018-09-15 Sat>"
+ ] =?>
+ mconcat [ headerWith ("important", mempty, mempty) 1 "important"
+ , plain $ strong "DEADLINE:"
+ <> space
+ <> emph (str "<2018-10-01 Mon>")
+ <> space
+ <> strong "SCHEDULED:"
+ <> space
+ <> emph (str "<2018-09-15 Sat>")
+ ]
+
+ , "empty planning info is not included" =:
+ T.unlines [ "#+OPTIONS: p:t"
+ , "* Wichtig"
+ ] =?>
+ headerWith ("wichtig", mempty, mempty) 1 "Wichtig"
+ ]
]
, testGroup "Include"
diff --git a/test/Tests/Readers/Org/Inline.hs b/test/Tests/Readers/Org/Inline.hs
index 07fe2d2e9..9cfcda79f 100644
--- a/test/Tests/Readers/Org/Inline.hs
+++ b/test/Tests/Readers/Org/Inline.hs
@@ -96,7 +96,7 @@ tests =
"[fn::Schreib mir eine E-Mail]" =?>
para (note $ para "Schreib mir eine E-Mail")
- , "Markup-chars not occuring on word break are symbols" =:
+ , "Markup-chars not occurring on word break are symbols" =:
T.unlines [ "this+that+ +so+on"
, "seven*eight* nine*"
, "+not+funny+"
@@ -280,6 +280,13 @@ tests =
)
"echo 'Hello, World'")
+ , "Inline code block with a blank argument array" =:
+ "src_sh[]{echo 'Hello, World'}" =?>
+ para (codeWith ( ""
+ , [ "bash" ]
+ , [ ("org-language", "sh") ])
+ "echo 'Hello, World'")
+
, "Inline code block with toggle" =:
"src_sh[:toggle]{echo $HOME}" =?>
para (codeWith ( ""
diff --git a/test/Tests/Readers/RST.hs b/test/Tests/Readers/RST.hs
index 906ed4ff9..963e7530d 100644
--- a/test/Tests/Readers/RST.hs
+++ b/test/Tests/Readers/RST.hs
@@ -177,7 +177,7 @@ tests = [ "line block with blank line" =:
=: ".. 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"))
+ para (codeWith ("",["interpreted-text"],[("role","unknown")]) "text")
]
, testGroup "footnotes"
[ "remove space before note" =: T.unlines
@@ -188,4 +188,18 @@ tests = [ "line block with blank line" =:
] =?>
para ("foo" <> note (para "bar"))
]
+ , testGroup "inlines"
+ [ "links can contain an URI without being parsed twice (#4581)" =:
+ "`http://loc <http://loc>`__" =?>
+ para (link "http://loc" "" "http://loc")
+ , "inline markup cannot be nested" =:
+ "**a*b*c**" =?>
+ para (strong "a*b*c")
+ , "bare URI parsing disabled inside emphasis (#4561)" =:
+ "*http://location*" =?>
+ para (emph (text "http://location"))
+ , "include newlines" =:
+ "**before\nafter**" =?>
+ para (strong (text "before\nafter"))
+ ]
]