diff options
Diffstat (limited to 'tests/Tests/Readers')
-rw-r--r-- | tests/Tests/Readers/Docx.hs | 127 | ||||
-rw-r--r-- | tests/Tests/Readers/EPUB.hs | 33 | ||||
-rw-r--r-- | tests/Tests/Readers/Markdown.hs | 71 | ||||
-rw-r--r-- | tests/Tests/Readers/Org.hs | 74 | ||||
-rw-r--r-- | tests/Tests/Readers/Txt2Tags.hs | 430 |
5 files changed, 714 insertions, 21 deletions
diff --git a/tests/Tests/Readers/Docx.hs b/tests/Tests/Readers/Docx.hs index ffb079eee..c310cc8d7 100644 --- a/tests/Tests/Readers/Docx.hs +++ b/tests/Tests/Readers/Docx.hs @@ -5,10 +5,15 @@ import Text.Pandoc.Readers.Native import Text.Pandoc.Definition import Tests.Helpers import Test.Framework +import Test.HUnit (assertBool) +import Test.Framework.Providers.HUnit import qualified Data.ByteString.Lazy as B import Text.Pandoc.Readers.Docx import Text.Pandoc.Writers.Native (writeNative) import qualified Data.Map as M +import Text.Pandoc.MediaBag (MediaBag, lookupMedia, mediaDirectory) +import Codec.Archive.Zip +import System.FilePath (combine) -- We define a wrapper around pandoc that doesn't normalize in the -- tests. Since we do our own normalization, we want to make sure @@ -37,7 +42,8 @@ compareOutput :: ReaderOptions compareOutput opts docxFile nativeFile = do df <- B.readFile docxFile nf <- Prelude.readFile nativeFile - return $ (noNorm (readDocx opts df), noNorm (readNative nf)) + let (p, _) = readDocx opts df + return $ (noNorm p, noNorm (readNative nf)) testCompareWithOptsIO :: ReaderOptions -> String -> FilePath -> FilePath -> IO Test testCompareWithOptsIO opts name docxFile nativeFile = do @@ -51,6 +57,44 @@ testCompareWithOpts opts name docxFile nativeFile = testCompare :: String -> FilePath -> FilePath -> Test testCompare = testCompareWithOpts def +getMedia :: FilePath -> FilePath -> IO (Maybe B.ByteString) +getMedia archivePath mediaPath = do + zf <- B.readFile archivePath >>= return . toArchive + return $ findEntryByPath (combine "word" mediaPath) zf >>= (Just . fromEntry) + +compareMediaPathIO :: FilePath -> MediaBag -> FilePath -> IO Bool +compareMediaPathIO mediaPath mediaBag docxPath = do + docxMedia <- getMedia docxPath mediaPath + let mbBS = case lookupMedia mediaPath mediaBag of + Just (_, bs) -> bs + Nothing -> error ("couldn't find " ++ + mediaPath ++ + " in media bag") + docxBS = case docxMedia of + Just bs -> bs + Nothing -> error ("couldn't find " ++ + mediaPath ++ + " in media bag") + return $ mbBS == docxBS + +compareMediaBagIO :: FilePath -> IO Bool +compareMediaBagIO docxFile = do + df <- B.readFile docxFile + let (_, mb) = readDocx def df + bools <- mapM + (\(fp, _, _) -> compareMediaPathIO fp mb docxFile) + (mediaDirectory mb) + return $ and bools + +testMediaBagIO :: String -> FilePath -> IO Test +testMediaBagIO name docxFile = do + outcome <- compareMediaBagIO docxFile + return $ testCase name (assertBool + ("Media didn't match media bag in file " ++ docxFile) + outcome) + +testMediaBag :: String -> FilePath -> Test +testMediaBag name docxFile = buildTest $ testMediaBagIO name docxFile tests :: [Test] tests = [ testGroup "inlines" @@ -63,10 +107,14 @@ tests = [ testGroup "inlines" "docx.links.docx" "docx.links.native" , testCompare - "inline image with reference output" + "inline image" "docx.image.docx" "docx.image_no_embed.native" , testCompare + "inline image in links" + "docx.inline_images.docx" + "docx.inline_images.native" + , testCompare "handling unicode input" "docx.unicode.docx" "docx.unicode.native" @@ -82,6 +130,14 @@ tests = [ testGroup "inlines" "normalizing inlines deep inside blocks" "docx.deep_normalize.docx" "docx.deep_normalize.native" + , testCompare + "move trailing spaces outside of formatting" + "docx.trailing_spaces_in_formatting.docx" + "docx.trailing_spaces_in_formatting.native" + , testCompare + "inline code (with VerbatimChar style)" + "docx.inline_code.docx" + "docx.inline_code.native" ] , testGroup "blocks" [ testCompare @@ -89,10 +145,18 @@ tests = [ testGroup "inlines" "docx.headers.docx" "docx.headers.native" , testCompare + "headers already having auto identifiers" + "docx.already_auto_ident.docx" + "docx.already_auto_ident.native" + , testCompare "lists" "docx.lists.docx" "docx.lists.native" , testCompare + "definition lists" + "docx.definition_list.docx" + "docx.definition_list.native" + , testCompare "footnotes and endnotes" "docx.notes.docx" "docx.notes.native" @@ -101,9 +165,68 @@ tests = [ testGroup "inlines" "docx.block_quotes.docx" "docx.block_quotes_parse_indent.native" , testCompare + "hanging indents" + "docx.hanging_indent.docx" + "docx.hanging_indent.native" + , testCompare "tables" "docx.tables.docx" "docx.tables.native" + , testCompare + "code block" + "docx.codeblock.docx" + "docx.codeblock.native" + + ] + , testGroup "track changes" + [ testCompare + "insertion (default)" + "docx.track_changes_insertion.docx" + "docx.track_changes_insertion_accept.native" + , testCompareWithOpts def{readerTrackChanges=AcceptChanges} + "insert insertion (accept)" + "docx.track_changes_insertion.docx" + "docx.track_changes_insertion_accept.native" + , testCompareWithOpts def{readerTrackChanges=RejectChanges} + "remove insertion (reject)" + "docx.track_changes_insertion.docx" + "docx.track_changes_insertion_reject.native" + , testCompare + "deletion (default)" + "docx.track_changes_deletion.docx" + "docx.track_changes_deletion_accept.native" + , testCompareWithOpts def{readerTrackChanges=AcceptChanges} + "remove deletion (accept)" + "docx.track_changes_deletion.docx" + "docx.track_changes_deletion_accept.native" + , testCompareWithOpts def{readerTrackChanges=RejectChanges} + "insert deletion (reject)" + "docx.track_changes_deletion.docx" + "docx.track_changes_deletion_reject.native" + , testCompareWithOpts def{readerTrackChanges=AllChanges} + "keep insertion (all)" + "docx.track_changes_deletion.docx" + "docx.track_changes_deletion_all.native" + , testCompareWithOpts def{readerTrackChanges=AllChanges} + "keep deletion (all)" + "docx.track_changes_deletion.docx" + "docx.track_changes_deletion_all.native" ] + , testGroup "media" + [ testMediaBag + "image extraction" + "docx.image.docx" + ] + , testGroup "metadata" + [ testCompareWithOpts def{readerStandalone=True} + "metadata fields" + "docx.metadata.docx" + "docx.metadata.native" + , testCompareWithOpts def{readerStandalone=True} + "stop recording metadata with normal text" + "docx.metadata_after_normal.docx" + "docx.metadata_after_normal.native" + ] + ] diff --git a/tests/Tests/Readers/EPUB.hs b/tests/Tests/Readers/EPUB.hs new file mode 100644 index 000000000..01b68082b --- /dev/null +++ b/tests/Tests/Readers/EPUB.hs @@ -0,0 +1,33 @@ +module Tests.Readers.EPUB (tests) where + +import Text.Pandoc.Options +import Test.Framework +import Test.HUnit (assertBool) +import Test.Framework.Providers.HUnit +import qualified Data.ByteString.Lazy as BL +import Text.Pandoc.Readers.EPUB +import Text.Pandoc.MediaBag (MediaBag, mediaDirectory) +import Control.Applicative + +getMediaBag :: FilePath -> IO MediaBag +getMediaBag fp = snd . readEPUB def <$> BL.readFile fp + +testMediaBag :: FilePath -> [(String, String, Int)] -> IO () +testMediaBag fp bag = do + actBag <- (mediaDirectory <$> getMediaBag fp) + assertBool (show "MediaBag did not match:\nExpected: " + ++ show bag + ++ "\nActual: " + ++ show actBag) + (actBag == bag) + +featuresBag :: [(String, String, Int)] +featuresBag = [("img/ElementaryMathExample.png","image/png",1331),("img/Maghreb1.png","image/png",2520),("img/check.gif","image/gif",1340),("img/check.jpg","image/jpeg",2661),("img/check.png","image/png",2815),("img/cichons_diagram.png","image/png",7045),("img/complex_number.png","image/png",5238),("img/multiscripts_and_greek_alphabet.png","image/png",10060)] + +tests :: [Test] +tests = + [ testGroup "EPUB Mediabag" + [ testCase "features bag" + (testMediaBag "epub.features.epub" featuresBag) + ] + ] diff --git a/tests/Tests/Readers/Markdown.hs b/tests/Tests/Readers/Markdown.hs index 5a51fe759..6e64a6f15 100644 --- a/tests/Tests/Readers/Markdown.hs +++ b/tests/Tests/Readers/Markdown.hs @@ -16,6 +16,10 @@ markdown = readMarkdown def markdownSmart :: String -> Pandoc markdownSmart = readMarkdown def { readerSmart = True } +markdownCDL :: String -> Pandoc +markdownCDL = readMarkdown def { readerExtensions = Set.insert + Ext_compact_definition_lists $ readerExtensions def } + infix 4 =: (=:) :: ToString c => String -> (String, c) -> Test @@ -140,11 +144,28 @@ tests = [ testGroup "inline code" [ "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" <> space <> + 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)" =: + "<del>test</del>" =?> + rawBlock "html" "<del>" <> plain (str "test") <> + rawBlock "html" "</del>" + ] , "unbalanced brackets" =: "[[[[[[[[[[[[[[[hi" =?> para (text "[[[[[[[[[[[[[[[hi") , testGroup "backslash escapes" @@ -179,17 +200,6 @@ tests = [ testGroup "inline code" ("À l'arrivée de la guerre, le thème de l'«impossibilité du socialisme»" =?> para "À l’arrivée de la guerre, le thème de l’«impossibilité du socialisme»") ] - , testGroup "mixed emphasis and strong" - [ "emph and strong emph alternating" =: - "*xxx* ***xxx*** xxx\n*xxx* ***xxx*** xxx" - =?> para (emph "xxx" <> space <> strong (emph "xxx") <> - space <> "xxx" <> space <> - emph "xxx" <> space <> strong (emph "xxx") <> - space <> "xxx") - , "emph with spaced strong" =: - "*x **xx** x*" - =?> para (emph ("x" <> space <> strong "xx" <> space <> "x")) - ] , testGroup "footnotes" [ "indent followed by newline and flush-left text" =: "[^1]\n\n[^1]: my note\n\n \nnot in note\n" @@ -216,13 +226,50 @@ tests = [ testGroup "inline code" -- , 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 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")]) + ] + ] + , testGroup "+compact_definition_lists" + [ test markdownCDL "basic compact list" $ + "foo1\n: bar\n baz\nfoo2\n: bar2\n" =?> + definitionList [ (text "foo1", [plain (text "bar baz")]) + , (text "foo2", [plain (text "bar2")]) + ] + ] , testGroup "lists" [ "issue #1154" =: " - <div>\n first div breaks\n </div>\n\n <button>if this button exists</button>\n\n <div>\n with this div too.\n </div>\n" =?> bulletList [divWith nullAttr (plain $ text "first div breaks") <> rawBlock "html" "<button>" <> plain (text "if this button exists") <> - rawBlock "html" "</button>\n" <> + rawBlock "html" "</button>" <> divWith nullAttr (plain $ text "with this div too.")] ] ] diff --git a/tests/Tests/Readers/Org.hs b/tests/Tests/Readers/Org.hs index f8240ca3d..cc4e495f3 100644 --- a/tests/Tests/Readers/Org.hs +++ b/tests/Tests/Readers/Org.hs @@ -593,7 +593,7 @@ tests = " + Technologic\n" ++ " + Robot Rock\n") =?> bulletList [ mconcat - [ para "Discovery" + [ plain "Discovery" , bulletList [ plain ("One" <> space <> "More" <> space <> "Time") @@ -604,14 +604,14 @@ tests = ] ] , mconcat - [ para "Homework" + [ plain "Homework" , bulletList [ plain ("Around" <> space <> "the" <> space <> "World") ] ] , mconcat - [ para ("Human" <> space <> "After" <> space <> "All") + [ plain ("Human" <> space <> "After" <> space <> "All") , bulletList [ plain "Technologic" , plain ("Robot" <> space <> "Rock") ] @@ -654,13 +654,13 @@ tests = " 2. Two-Two\n") =?> let listStyle = (1, DefaultStyle, DefaultDelim) listStructure = [ mconcat - [ para "One" + [ plain "One" , orderedList [ plain "One-One" , plain "One-Two" ] ] , mconcat - [ para "Two" + [ plain "Two" , orderedList [ plain "Two-One" , plain "Two-Two" ] @@ -671,14 +671,14 @@ tests = , "Ordered List in Bullet List" =: ("- Emacs\n" ++ " 1. Org\n") =?> - bulletList [ (para "Emacs") <> + bulletList [ (plain "Emacs") <> (orderedList [ plain "Org"]) ] , "Bullet List in Ordered List" =: ("1. GNU\n" ++ " - Freedom\n") =?> - orderedList [ (para "GNU") <> bulletList [ (plain "Freedom") ] ] + orderedList [ (plain "GNU") <> bulletList [ (plain "Freedom") ] ] , "Definition List" =: unlines [ "- PLL :: phase-locked loop" @@ -886,6 +886,66 @@ tests = , " (+ 23 42))" ] in codeBlockWith ("", classes, params) code' + , "Source block with results and :exports both" =: + unlines [ "#+BEGIN_SRC emacs-lisp :exports both" + , "(progn (message \"Hello, World!\")" + , " (+ 23 42))" + , "#+END_SRC" + , "" + , "#+RESULTS:" + , ": 65"] =?> + let classes = [ "commonlisp" -- as kate doesn't know emacs-lisp syntax + , "rundoc-block" + ] + params = [ ("rundoc-language", "emacs-lisp") + , ("rundoc-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" =: + unlines [ "#+BEGIN_SRC emacs-lisp :exports code" + , "(progn (message \"Hello, World!\")" + , " (+ 23 42))" + , "#+END_SRC" + , "" + , "#+RESULTS:" + , ": 65" ] =?> + let classes = [ "commonlisp" -- as kate doesn't know emacs-lisp syntax + , "rundoc-block" + ] + params = [ ("rundoc-language", "emacs-lisp") + , ("rundoc-exports", "code") + ] + code' = unlines [ "(progn (message \"Hello, World!\")" + , " (+ 23 42))" ] + in codeBlockWith ("", classes, params) code' + + , "Source block with results and :exports results" =: + 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" =: + unlines [ "#+BEGIN_SRC emacs-lisp :exports none" + , "(progn (message \"Hello, World!\")" + , " (+ 23 42))" + , "#+END_SRC" + , "" + , "#+RESULTS:" + , ": 65" ] =?> + rawBlock "html" "" + , "Example block" =: unlines [ "#+begin_example" , "A chosen representation of" diff --git a/tests/Tests/Readers/Txt2Tags.hs b/tests/Tests/Readers/Txt2Tags.hs new file mode 100644 index 000000000..4748cdc07 --- /dev/null +++ b/tests/Tests/Readers/Txt2Tags.hs @@ -0,0 +1,430 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Readers.Txt2Tags (tests) where + +import Text.Pandoc.Definition +import Test.Framework +import Tests.Helpers +import Tests.Arbitrary() +import Text.Pandoc.Builder +import Text.Pandoc +import Data.List (intersperse) +import Data.Monoid (mempty, mconcat) +import Text.Pandoc.Readers.Txt2Tags + +t2t :: String -> Pandoc +t2t s = readTxt2Tags (T2TMeta "date" "mtime" "in" "out") def ('\n' : s) + +infix 4 =: +(=:) :: ToString c + => String -> (String, c) -> Test +(=:) = test t2t + +spcSep :: [Inlines] -> Inlines +spcSep = mconcat . intersperse space + +simpleTable' :: Int + -> [Blocks] + -> [[Blocks]] + -> Blocks +simpleTable' n = table "" (take n $ repeat (AlignCenter, 0.0)) + +tests :: [Test] +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 "/", emph "_" + , strikeout "-", code "`", text "\"" + , rawInline "html" "'"]) + , "Markup must be greedy" =: + "********** ////////// __________ ---------- `````````` \"\"\"\"\"\"\"\"\"\" ''''''''''" =?> + para (spcSep [strong "******", emph "//////", emph "______" + , strikeout "------", code "``````", text "\"\"\"\"\"\"" + , rawInline "html" "''''''"]) + , "Inlines must be glued" =: + "** a** **a ** ** a **" =?> + para (text "** a** **a ** ** a **") + + , "Macros: Date" =: + "%%date" =?> + para "date" + , "Macros: Mod Time" =: + "%%mtime" =?> + para "mtime" + , "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")) + , "Image" =: + "[image.jpg]" =?> + para (image "image.jpg" "" 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 A blank line ends the 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. It 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" =: + 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" =: + unlines [ "lucky" + , "*star" + ] =?> + para ("lucky" <> space <> "*star") + + , "Horizontal Rule" =: + unlines [ "before" + , replicate 20 '-' + , replicate 20 '=' + , replicate 20 '_' + , "after" + ] =?> + mconcat [ para "before" + , horizontalRule + , horizontalRule + , horizontalRule + , para "after" + ] + + , "Comment Block" =: + 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" =: + 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" =: + 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" =: + unlines [ "| One |" + , "| Two |" + , "| Three |" + ] =?> + simpleTable' 1 mempty + [ [ plain "One" ] + , [ plain "Two" ] + , [ plain "Three" ] + ] + + , "Empty table" =: + "| |" =?> + simpleTable' 1 mempty [[mempty]] + + , "Glider Table" =: + 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" =: + 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" =: + 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" =: + 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" =: + unlines [ "```" + , "main = putStrLn greeting" + , " where greeting = \"moin\"" + , "```" ] =?> + let code' = "main = putStrLn greeting\n" ++ + " where greeting = \"moin\"\n" + in codeBlock code' + + , "tagged block" =: + unlines [ "'''" + , "<aside>HTML5 is pretty nice.</aside>" + , "'''" + ] =?> + rawBlock "html" "<aside>HTML5 is pretty nice.</aside>\n" + + , "Quote block" =: + unlines ["\t//Niemand// hat die Absicht, eine Mauer zu errichten!" + ] =?> + blockQuote (para (spcSep [ emph "Niemand", "hat", "die", "Absicht," + , "eine", "Mauer", "zu", "errichten!" + ])) + + ] + ] |