aboutsummaryrefslogtreecommitdiff
path: root/tests
diff options
context:
space:
mode:
Diffstat (limited to 'tests')
-rw-r--r--tests/Tests/Arbitrary.hs11
-rw-r--r--tests/Tests/Helpers.hs6
-rw-r--r--tests/Tests/Readers/RST.hs34
-rw-r--r--tests/Tests/Writers/Native.hs2
-rw-r--r--tests/testsuite.native4
5 files changed, 37 insertions, 20 deletions
diff --git a/tests/Tests/Arbitrary.hs b/tests/Tests/Arbitrary.hs
index d0000dcee..5939d088d 100644
--- a/tests/Tests/Arbitrary.hs
+++ b/tests/Tests/Arbitrary.hs
@@ -150,10 +150,13 @@ instance Arbitrary QuoteType where
instance Arbitrary Meta where
arbitrary
- = do x1 <- arbitrary
- x2 <- liftM (filter (not . null)) arbitrary
- x3 <- arbitrary
- return (Meta x1 x2 x3)
+ = do (x1 :: Inlines) <- arbitrary
+ (x2 :: [Inlines]) <- liftM (filter (not . isNull)) arbitrary
+ (x3 :: Inlines) <- arbitrary
+ return $ setMeta "title" x1
+ $ setMeta "author" x2
+ $ setMeta "date" x3
+ $ nullMeta
instance Arbitrary Alignment where
arbitrary
diff --git a/tests/Tests/Helpers.hs b/tests/Tests/Helpers.hs
index af64f5148..b48c8af3a 100644
--- a/tests/Tests/Helpers.hs
+++ b/tests/Tests/Helpers.hs
@@ -20,6 +20,7 @@ import Text.Pandoc.Options
import Text.Pandoc.Writers.Native (writeNative)
import qualified Test.QuickCheck.Property as QP
import Data.Algorithm.Diff
+import qualified Data.Map as M
test :: (ToString a, ToString b, ToString c)
=> (a -> b) -- ^ function to test
@@ -58,8 +59,9 @@ class ToString a where
instance ToString Pandoc where
toString d = writeNative def{ writerStandalone = s } $ toPandoc d
where s = case d of
- (Pandoc (Meta [] [] []) _) -> False
- _ -> True
+ (Pandoc (Meta m) _)
+ | M.null m -> False
+ | otherwise -> True
instance ToString Blocks where
toString = writeNative def . toPandoc
diff --git a/tests/Tests/Readers/RST.hs b/tests/Tests/Readers/RST.hs
index 2876f4270..a80dc32b7 100644
--- a/tests/Tests/Readers/RST.hs
+++ b/tests/Tests/Readers/RST.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE OverloadedStrings, ScopedTypeVariables #-}
module Tests.Readers.RST (tests) where
import Text.Pandoc.Definition
@@ -7,9 +7,10 @@ import Tests.Helpers
import Tests.Arbitrary()
import Text.Pandoc.Builder
import Text.Pandoc
+import Data.Monoid (mempty)
rst :: String -> Pandoc
-rst = readRST def
+rst = readRST def{ readerStandalone = True }
infix 4 =:
(=:) :: ToString c
@@ -21,14 +22,12 @@ tests = [ "line block with blank line" =:
"| a\n|\n| b" =?> para (str "a") <>
para (str "\160b")
, "field list" =: unlines
- [ ":Hostname: media08"
+ [ "para"
+ , ""
+ , ":Hostname: media08"
, ":IP address: 10.0.0.19"
, ":Size: 3ru"
- , ":Date: 2001-08-16"
, ":Version: 1"
- , ":Authors: - Me"
- , " - Myself"
- , " - I"
, ":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"
@@ -36,10 +35,9 @@ tests = [ "line block with blank line" =:
, ":Parameter i: integer"
, ":Final: item"
, " on two lines" ]
- =?> ( setAuthors ["Me","Myself","I"]
- $ setDate "2001-08-16"
- $ doc
- $ definitionList [ (str "Hostname", [para "media08"])
+ =?> ( doc
+ $ para "para" <>
+ definitionList [ (str "Hostname", [para "media08"])
, (str "IP address", [para "10.0.0.19"])
, (str "Size", [para "3ru"])
, (str "Version", [para "1"])
@@ -47,6 +45,20 @@ tests = [ "line block with blank line" =:
, (str "Parameter i", [para "integer"])
, (str "Final", [para "item on two lines"])
])
+ , "initial field list" =: unlines
+ [ "====="
+ , "Title"
+ , "====="
+ , "--------"
+ , "Subtitle"
+ , "--------"
+ , ""
+ , ":Version: 1"
+ ]
+ =?> ( setMeta "version" (para "1")
+ $ setMeta "title" ("Title" :: Inlines)
+ $ setMeta "subtitle" ("Subtitle" :: Inlines)
+ $ doc mempty )
, "URLs with following punctuation" =:
("http://google.com, http://yahoo.com; http://foo.bar.baz.\n" ++
"http://foo.bar/baz_(bam) (http://foo.bar)") =?>
diff --git a/tests/Tests/Writers/Native.hs b/tests/Tests/Writers/Native.hs
index e199cf94e..9833bf5ae 100644
--- a/tests/Tests/Writers/Native.hs
+++ b/tests/Tests/Writers/Native.hs
@@ -12,7 +12,7 @@ p_write_rt d =
p_write_blocks_rt :: [Block] -> Bool
p_write_blocks_rt bs = length bs > 20 ||
- read (writeNative def (Pandoc (Meta [] [] []) bs)) ==
+ read (writeNative def (Pandoc nullMeta bs)) ==
bs
tests :: [Test]
diff --git a/tests/testsuite.native b/tests/testsuite.native
index 90727a660..c10be2f5d 100644
--- a/tests/testsuite.native
+++ b/tests/testsuite.native
@@ -1,4 +1,4 @@
-Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docAuthors = [[Str "John",Space,Str "MacFarlane"],[Str "Anonymous"]], docDate = [Str "July",Space,Str "17,",Space,Str "2006"]})
+Pandoc {docMeta = Meta {unMeta = fromList [("author",MetaList [MetaBlocks [Plain [Str "John",Space,Str "MacFarlane"]],MetaBlocks [Plain [Str "Anonymous"]]]),("date",MetaBlocks [Plain [Str "July",Space,Str "17,",Space,Str "2006"]]),("title",MetaBlocks [Plain [Str "Pandoc",Space,Str "Test",Space,Str "Suite"]])]}, docBody =
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
,HorizontalRule
,Header 1 ("headers",[],[]) [Str "Headers"]
@@ -393,4 +393,4 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
[Para [Str "Notes",Space,Str "can",Space,Str "go",Space,Str "in",Space,Str "quotes.",Note [Para [Str "In",Space,Str "quote."]]]]
,OrderedList (1,Decimal,Period)
[[Plain [Str "And",Space,Str "in",Space,Str "list",Space,Str "items.",Note [Para [Str "In",Space,Str "list."]]]]]
-,Para [Str "This",Space,Str "paragraph",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "part",Space,Str "of",Space,Str "the",Space,Str "note,",Space,Str "as",Space,Str "it",Space,Str "is",Space,Str "not",Space,Str "indented."]]
+,Para [Str "This",Space,Str "paragraph",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "part",Space,Str "of",Space,Str "the",Space,Str "note,",Space,Str "as",Space,Str "it",Space,Str "is",Space,Str "not",Space,Str "indented."]]}