aboutsummaryrefslogtreecommitdiff
path: root/test
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2018-10-16 18:39:20 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2018-10-16 18:39:20 -0700
commit5c42101ee973131196b07661adc95670f2ed6693 (patch)
tree52ae302f981115a1855891d51857907704202ec7 /test
parent63b3886bfe3c5b50d171355573ab59750e009d03 (diff)
parent2c4e8941a7ccad2b325026fa27b9959ce959edef (diff)
downloadpandoc-5c42101ee973131196b07661adc95670f2ed6693.tar.gz
Merge branch 'groff_reader' of https://github.com/Yanpas/pandoc into Yanpas-groff_reader
Diffstat (limited to 'test')
-rw-r--r--test/Tests/Old.hs4
-rw-r--r--test/Tests/Readers/Man.hs83
-rw-r--r--test/grofftest.sh22
-rw-r--r--test/man-reader.man189
-rw-r--r--test/man-reader.native94
-rw-r--r--test/test-pandoc.hs2
6 files changed, 394 insertions, 0 deletions
diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs
index b426ffd07..842e0f656 100644
--- a/test/Tests/Old.hs
+++ b/test/Tests/Old.hs
@@ -171,6 +171,10 @@ tests = [ testGroup "markdown"
, test "tables" ["-f", "native", "-t", "../data/sample.lua"]
"tables.native" "tables.custom"
]
+ , testGroup "man"
+ [ test "reader" ["-r", "man", "-w", "native", "-s"]
+ "man-reader.man" "man-reader.native"
+ ]
]
-- makes sure file is fully closed after reading
diff --git a/test/Tests/Readers/Man.hs b/test/Tests/Readers/Man.hs
new file mode 100644
index 000000000..9dbfbab4d
--- /dev/null
+++ b/test/Tests/Readers/Man.hs
@@ -0,0 +1,83 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Readers.Man (tests) where
+
+import Prelude
+import Data.Text (Text)
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+import Text.Pandoc.Readers.Man
+
+man :: Text -> Pandoc
+man = purely $ readMan def
+
+infix 4 =:
+(=:) :: ToString c
+ => String -> (Text, c) -> TestTree
+(=:) = test man
+
+tests :: [TestTree]
+tests = [
+ -- .SH "HEllo bbb" "aaa"" as"
+ testGroup "Macros" [
+ "Bold" =:
+ ".B foo"
+ =?> (para $ strong "foo")
+ , "Italic" =:
+ ".I bar\n"
+ =?> (para $ emph "bar")
+ , "BoldItalic" =:
+ ".BI foo bar"
+ =?> (para $ strong $ emph $ str "foo bar")
+ , "H1" =:
+ ".SH The header\n"
+ =?> header 2 (str "The" <> space <> str "header")
+ , "H2" =:
+ ".SS \"The header 2\""
+ =?> header 3 (str "The header 2")
+ , "Macro args" =:
+ ".B \"single arg with \"\"Q\"\"\""
+ =?> (para $ strong $ str "single arg with \"Q\"")
+ , "comment" =:
+ ".\\\"bla\naaa"
+ =?> (para $ space <> str "aaa")
+ , "link" =:
+ ".BR aa (1)"
+ =?> (para $ link "../1/aa.1" "aa" (strong $ str "aa") <> (strong $ str " (1)"))
+ ],
+ testGroup "Escapes" [
+ "fonts" =:
+ "aa\\fIbb\\fRcc"
+ =?> (para $ str "aa" <> (emph $ str "bb") <> str "cc")
+ , "skip" =:
+ "a\\%\\{\\}\\\n\\:b\\0"
+ =?> (para $ str "ab")
+ , "replace" =:
+ "\\-\\ \\\\\\[lq]\\[rq]\\[em]\\[en]\\*(lq\\*(rq"
+ =?> (para $ str "- \\“”—–«»")
+ , "replace2" =:
+ "\\t\\e\\`\\^\\|\\'"
+ =?> (para $ str "\t\\` `")
+ ],
+ testGroup "Lists" [
+ "bullet" =:
+ ".IP\nfirst\n.IP\nsecond"
+ =?> bulletList [plain $ str "first", plain $ str "second"]
+ , "odrered" =:
+ ".IP 1 a\nfirst\n.IP 2 a\nsecond"
+ =?> orderedListWith (1,Decimal,DefaultDelim) [plain $ str "first", plain $ str "second"]
+ , "upper" =:
+ ".IP A a\nfirst\n.IP B a\nsecond"
+ =?> orderedListWith (1,UpperAlpha,DefaultDelim) [plain $ str "first", plain $ str "second"]
+ , "nested" =:
+ ".IP\nfirst\n.RS\n.IP\n1a\n.IP\n1b\n.RE"
+ =?> bulletList [(plain $ str "first") <> (bulletList [plain $ str "1a", plain $ str "1b"])]
+ ],
+ testGroup "CodeBlocks" [
+ "cb1"=:
+ ".nf\naa\n\tbb\n.fi"
+ =?> codeBlock "aa\n\tbb"
+ ]
+ ]
diff --git a/test/grofftest.sh b/test/grofftest.sh
new file mode 100644
index 000000000..ca1aa71d9
--- /dev/null
+++ b/test/grofftest.sh
@@ -0,0 +1,22 @@
+#!/bin/bash
+
+# iterates over specified directory, containing "\w+\.\d"-like files,
+# executes pandoc voer them and prints stderr on nonzero return code
+
+if [ $# -ne 2 ]; then
+ echo "Not enough arguments"
+ exit 1
+fi
+
+PANDOC=$1
+DIR=$2
+
+$PANDOC --version > /dev/null || { echo "pandoc executable error" >&2 ; exit 1 ; }
+
+ls $2 | egrep "^.+\.[0-9].?$" | while read f ; do
+ FILE="$DIR/$f"
+ $PANDOC -f man -t native < $FILE 2>&1 > /dev/null
+ if [ $? -ne 0 ]; then
+ echo "Failed to convert $FILE"
+ fi
+done
diff --git a/test/man-reader.man b/test/man-reader.man
new file mode 100644
index 000000000..4f3395051
--- /dev/null
+++ b/test/man-reader.man
@@ -0,0 +1,189 @@
+.TH "Pandoc Man tests" "" "Oct 17, 2018" "" ""
+.PP
+This is a set of tests for pandoc.
+.PP
+ * * * * *
+.SH Headers
+.SH Level 1
+.SS Level 2
+
+ * * * * *
+.SH Paragraphs
+.PP
+Here's a regular paragraph.
+.PP
+Another 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.
+.PP
+There should be a hard line break
+.PD 0
+.P
+.PD
+here.
+.PP
+ * * * * *
+.SH Block Quotes
+Code in a block quote:
+.IP
+.nf
+\f[C]
+sub\ status\ {
+\ \ \ \ print\ "working";
+}
+\f[]
+.fi
+.PP
+A list:
+.IP "1." 3
+item one
+.IP "2." 3
+item two
+.PP
+.SH Code Blocks
+.PP
+Code:
+.IP
+.nf
+\f[C]
+\-\-\-\-\ (should\ be\ four\ hyphens)
+
+sub\ status\ {
+\ \ \ \ print\ "working";
+}
+
+\f[]
+.fi
+.PP
+And:
+.IP
+.nf
+\f[C]
+\tthis\ code\ line is\ indented\ by\ one\ tab
+
+These\ should\ not\ be\ escaped:\ \ \\$\ \\\\\ \\>\ \\[\ \\{
+\f[]
+.fi
+.PP
+ * * * * *
+.SH Lists
+.SS Unordered
+.PP
+Asterisks:
+.IP \[bu] 2
+asterisk 1
+.IP \[bu] 2
+asterisk 2
+.IP \[bu] 2
+asterisk 3
+.PP
+.SS Ordered
+.IP "1." 3
+First
+.IP "2." 3
+Second
+.IP "3." 3
+Third
+.PP
+.SS Nested
+.IP \[bu] 2
+Tab
+.RS 2
+.IP \[bu] 2
+Tab
+.RS 2
+.IP \[bu] 2
+Tab
+.RE
+.RE
+.PP
+Here's another:
+.IP "1." 3
+First
+.IP "2." 3
+Second:
+.RS 4
+.IP \[bu] 2
+Fee
+.IP \[bu] 2
+Fie
+.IP \[bu] 2
+Foe
+.RE
+.IP "3." 3
+Third
+.PP
+Same thing:
+.IP "1." 3
+First
+.IP "2." 3
+Second:
+.RS 4
+.IP \[bu] 2
+Fee
+.IP \[bu] 2
+Fie
+.IP \[bu] 2
+Foe
+.RE
+.IP "3." 3
+Third
+.SS different styles:
+.IP "A." 3
+Upper Alpha
+.RS 4
+.IP "I." 3
+Upper Roman.
+.RS 4
+.IP "(6)" 4
+Decimal start with 6
+.RS 4
+.IP "c)" 3
+Lower alpha with paren
+.RE
+.RE
+.RE
+.PP
+ * * * * *
+.SH Special Characters
+AT&T has an ampersand in their name.
+.PP
+4 < 5.
+.PP
+6 > 5.
+.PP
+Backslash: \\
+.PP
+Backtick: `
+.PP
+Asterisk: *
+.PP
+Underscore: _
+.PP
+Left brace: {
+.PP
+Right brace: }
+.PP
+Left bracket: [
+.PP
+Right bracket: ]
+.PP
+Left paren: (
+.PP
+Right paren: )
+.PP
+Greater\-than: >
+.PP
+Hash: #
+.PP
+Period: .
+.PP
+Bang: !
+.PP
+Plus: +
+.PP
+Minus: \-
+.PP
diff --git a/test/man-reader.native b/test/man-reader.native
new file mode 100644
index 000000000..1fa010bd6
--- /dev/null
+++ b/test/man-reader.native
@@ -0,0 +1,94 @@
+Pandoc (Meta {unMeta = fromList [("title",MetaString "Pandoc Man tests")]})
+[Header 1 ("",[],[]) [Str "Pandoc Man tests"]
+,Para [Str "This is a set of tests for pandoc."]
+,Para [Str " * * * * *"]
+,Header 2 ("",[],[]) [Str "Headers"]
+,Header 2 ("",[],[]) [Str "Level",Space,Str "1"]
+,Header 3 ("",[],[]) [Str "Level",Space,Str "2"]
+,Para [Str " * * * * *"]
+,Header 2 ("",[],[]) [Str "Paragraphs"]
+,Para [Str "Here's a regular paragraph."]
+,Para [Str "Another paragraph",Space,Str "In Markdown 1.0.0 and earlier.",Space,Str "Version 8.",Space,Str "This line turns into a list item.",Space,Str "Because a hard-wrapped line in the middle of a paragraph looked like a list",Space,Str "item."]
+,Para [Str "There should be a hard line break"]
+,Para [Str "here."]
+,Para [Str " * * * * *"]
+,Header 2 ("",[],[]) [Str "Block",Space,Str "Quotes"]
+,Para [Str "Code in a block quote:"]
+,CodeBlock ("",[],[]) "\nsub status {\n print \"working\";\n}\n"
+,Para [Str "A list:"]
+,OrderedList (1,Decimal,DefaultDelim)
+ [[Plain [Str "item one"]]
+ ,[Plain [Str "item two"]]]
+,Header 2 ("",[],[]) [Str "Code",Space,Str "Blocks"]
+,Para [Str "Code:"]
+,CodeBlock ("",[],[]) "\n---- (should be four hyphens)\n\nsub status {\n print \"working\";\n}\n\n"
+,Para [Str "And:"]
+,CodeBlock ("",[],[]) "\n\tthis code line is indented by one tab\n\nThese should not be escaped: \\$ \\\\ \\> \\[ \\{\n"
+,Para [Str " * * * * *"]
+,Header 2 ("",[],[]) [Str "Lists"]
+,Header 3 ("",[],[]) [Str "Unordered"]
+,Para [Str "Asterisks:"]
+,BulletList
+ [[Plain [Str "",Space,Str "asterisk 1"]]
+ ,[Plain [Str "",Space,Str "asterisk 2"]]
+ ,[Plain [Str "",Space,Str "asterisk 3"]]]
+,Header 3 ("",[],[]) [Str "Ordered"]
+,OrderedList (1,Decimal,DefaultDelim)
+ [[Plain [Str "First"]]
+ ,[Plain [Str "Second"]]
+ ,[Plain [Str "Third"]]]
+,Header 3 ("",[],[]) [Str "Nested"]
+,BulletList
+ [[Plain [Str "",Space,Str "Tab"]
+ ,BulletList
+ [[Plain [Str "",Space,Str "Tab"]
+ ,BulletList
+ [[Plain [Str "",Space,Str "Tab"]]]]]]]
+,Para [Str "Here's another:"]
+,OrderedList (1,Decimal,DefaultDelim)
+ [[Plain [Str "First"]]
+ ,[Plain [Str "Second:"]
+ ,BulletList
+ [[Plain [Str "",Space,Str "Fee"]]
+ ,[Plain [Str "",Space,Str "Fie"]]
+ ,[Plain [Str "",Space,Str "Foe"]]]]
+ ,[Plain [Str "Third"]]]
+,Para [Str "Same thing:"]
+,OrderedList (1,Decimal,DefaultDelim)
+ [[Plain [Str "First"]]
+ ,[Plain [Str "Second:"]
+ ,BulletList
+ [[Plain [Str "",Space,Str "Fee"]]
+ ,[Plain [Str "",Space,Str "Fie"]]
+ ,[Plain [Str "",Space,Str "Foe"]]]]
+ ,[Plain [Str "Third"]]]
+,Header 3 ("",[],[]) [Str "different",Space,Str "styles:"]
+,OrderedList (1,UpperAlpha,DefaultDelim)
+ [[Plain [Str "Upper Alpha"]
+ ,OrderedList (1,UpperAlpha,DefaultDelim)
+ [[Plain [Str "Upper Roman."]
+ ,BulletList
+ [[Plain [Str "(6)",Space,Str "Decimal start with 6"]
+ ,OrderedList (1,LowerAlpha,DefaultDelim)
+ [[Plain [Str "Lower alpha with paren"]]]]]]]]]
+,Para [Str " * * * * *"]
+,Header 2 ("",[],[]) [Str "Special",Space,Str "Characters"]
+,Para [Str "AT&T has an ampersand in their name."]
+,Para [Str "4 < 5."]
+,Para [Str "6 > 5."]
+,Para [Str "Backslash: \\"]
+,Para [Str "Backtick: `"]
+,Para [Str "Asterisk: *"]
+,Para [Str "Underscore: _"]
+,Para [Str "Left brace: {"]
+,Para [Str "Right brace: }"]
+,Para [Str "Left bracket: ["]
+,Para [Str "Right bracket: ]"]
+,Para [Str "Left paren: ("]
+,Para [Str "Right paren: )"]
+,Para [Str "Greater-than: >"]
+,Para [Str "Hash: #"]
+,Para [Str "Period: ."]
+,Para [Str "Bang: !"]
+,Para [Str "Plus: +"]
+,Para [Str "Minus: -"]]
diff --git a/test/test-pandoc.hs b/test/test-pandoc.hs
index b70d2286c..dc51b73cc 100644
--- a/test/test-pandoc.hs
+++ b/test/test-pandoc.hs
@@ -22,6 +22,7 @@ import qualified Tests.Readers.Odt
import qualified Tests.Readers.Org
import qualified Tests.Readers.RST
import qualified Tests.Readers.Txt2Tags
+import qualified Tests.Readers.Man
import qualified Tests.Shared
import qualified Tests.Writers.AsciiDoc
import qualified Tests.Writers.ConTeXt
@@ -76,6 +77,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 "Man" Tests.Readers.Man.tests
, testGroup "FB2" Tests.Readers.FB2.tests
]
, testGroup "Lua filters" Tests.Lua.tests