{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{- |
Module : Tests.Readers.DokuWiki
Copyright : © 2018-2020 Alexander Krotov
License : GNU GPL, version 2 or above
Maintainer : Alexander Krotov
Stability : alpha
Portability : portable
Tests for DokuWiki reader.
-}
module Tests.Readers.DokuWiki (tests) where
import Prelude
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
dokuwiki :: Text -> Pandoc
dokuwiki = purely $ readDokuWiki def{ readerStandalone = True }
infix 4 =:
(=:) :: ToString c
=> String -> (Text, c) -> TestTree
(=:) = test dokuwiki
tests :: [TestTree]
tests = [ testGroup "inlines"
[ "Bold" =:
"**bold**" =?>
para (strong "bold")
, "Italic" =:
"//italic//" =?>
para (emph "italic")
, "Underlined" =:
"__underlined__" =?>
para (underline "underlined")
, "Monospaced" =:
"''monospaced''" =?>
para (code "monospaced")
, "Monospaced with nowiki" =:
"''%%monospaced%%''" =?>
para (code "monospaced")
, "Combined" =:
"**__//''combine''//__**" =?>
para (strong $ underline $ emph $ code "combine")
, "Nowiki" =:
T.unlines [ " Hello Worlddeleted" =?>
para (strikeout "deleted")
, "Inline code" =:
"foo public static void main
bar" =?>
para (text "foo " <> codeWith ("", ["java"], []) "public static void main" <> text " bar")
, "Inline file" =:
"foo
Hello World
';") , "Linebreak" =: T.unlines [ "This is some text with some linebreaks\\\\ Note that the" , "two backslashes are only recognized at the end of a line\\\\" , "or followed by\\\\ a whitespace \\\\this happens without it." ] =?> para ("This is some text with some linebreaks" <> linebreak <> "Note that the\n" <> "two backslashes are only recognized at the end of a line" <> linebreak <> "or followed by" <> linebreak <> "a whitespace \\\\this happens without it.") , testGroup "External links" [ "Autolink" =: "http://www.google.com" =?> para (link "http://www.google.com" "" (str "http://www.google.com")) , "Link without description" =: "[[https://example.com]]" =?> para (link "https://example.com" "" (str "https://example.com")) , "Link with description" =: "[[http://www.google.com|This Link points to google]]" =?> para (link "http://www.google.com" "" (text "This Link points to google")) , "Trim whitespace around link and description" =: "[[ http://www.google.com | This Link points to google ]]" =?> para (link "http://www.google.com" "" (text "This Link points to google")) , "Email address" =: ""
, "some code"
, "comes here"
, "
"
, " - fourth item"
] =?>
orderedList [ plain "first item"
, plain ("second item with linebreak" <> linebreak <> " second line")
, plain ("third item with code: " <> code "some code\ncomes here\n")
, plain "fourth item"
]
]
, "Block HTML" =:
T.unlines [ ""
, "And this is some block HTML
" , "" ] =?> rawBlock "html" "And this is some block HTML
\n" , "Block PHP" =: T.unlines [ "Hello World
';" , "Hello World
';\n" , "Quote" =: T.unlines [ "> foo" , ">no space is required after >" , "> bar" , ">> baz" , "> bat" ] =?> blockQuote (plain "foo" <> plain "no space is required after >" <> plain "bar" <> blockQuote (plain "baz") <> plain "bat") , "Code block" =: T.unlines [ ""
, "foo bar baz"
, "
"
] =?>
codeBlock "foo bar baz\n"
, "Java code block" =:
T.unlines [ ""
, "public static void main"
, "
"
] =?>
codeBlockWith ("", ["java"], []) "public static void main\n"
, "File with filename and no language" =:
T.unlines [ "