Updated tests for new native format.
This commit is contained in:
parent
8894b1a030
commit
52b6e38425
14 changed files with 2240 additions and 2332 deletions
|
@ -12,6 +12,7 @@ import System.Exit
|
|||
import Data.Algorithm.Diff
|
||||
import Text.Pandoc.Shared ( substitute, normalize, defaultWriterOptions )
|
||||
import Text.Pandoc.Writers.Native ( writeNative )
|
||||
import Text.Pandoc.Readers.Native ( readNative )
|
||||
import Text.Pandoc.Highlighting ( languages )
|
||||
import Prelude hiding ( readFile )
|
||||
import qualified Data.ByteString.Lazy as B
|
||||
|
@ -128,7 +129,7 @@ lhsReaderTest :: String -> Test
|
|||
lhsReaderTest format =
|
||||
testWithNormalize normalizer "lhs" ["-r", format, "-w", "native"]
|
||||
("lhs-test" <.> format) "lhs-test.native"
|
||||
where normalizer = writeNative defaultWriterOptions . normalize . read
|
||||
where normalizer = writeNative defaultWriterOptions . normalize . readNative
|
||||
|
||||
latexCitationTests :: String -> Test
|
||||
latexCitationTests n
|
||||
|
|
|
@ -23,7 +23,6 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,Para [Str "E",Str "-",Str "mail",Space,Str "style:"]
|
||||
,BlockQuote
|
||||
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "block",Space,Str "quote",Str ".",Space,Str "It",Space,Str "is",Space,Str "pretty",Space,Str "short",Str "."]]
|
||||
|
||||
,BlockQuote
|
||||
[Para [Str "Code",Space,Str "in",Space,Str "a",Space,Str "block",Space,Str "quote:"]
|
||||
,CodeBlock ("",[],[]) "sub status {\n print \"working\";\n}"
|
||||
|
@ -34,10 +33,8 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,Para [Str "Nested",Space,Str "block",Space,Str "quotes:"]
|
||||
,BlockQuote
|
||||
[Para [Str "nested"]]
|
||||
|
||||
,BlockQuote
|
||||
[ Para [Str "nested"] ]
|
||||
]
|
||||
[Para [Str "nested"]]]
|
||||
,Para [Str "This",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "a",Space,Str "block",Space,Str "quote:",Space,Str "2",Space,Str ">",Space,Str "1",Str "."]
|
||||
,Para [Str "Box",Str "-",Str "style:"]
|
||||
,BlockQuote
|
||||
|
@ -51,8 +48,7 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,BlockQuote
|
||||
[Para [Str "Joe",Space,Str "said:"]
|
||||
,BlockQuote
|
||||
[ Para [Str "Don",Str "'",Str "t",Space,Str "quote",Space,Str "me",Str "."] ]
|
||||
]
|
||||
[Para [Str "Don",Str "'",Str "t",Space,Str "quote",Space,Str "me",Str "."]]]
|
||||
,Para [Str "And",Space,Str "a",Space,Str "following",Space,Str "paragraph",Str "."]
|
||||
,HorizontalRule
|
||||
,Header 1 [Str "Code",Space,Str "Blocks"]
|
||||
|
@ -117,7 +113,8 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,Para [Str "Multiple",Space,Str "paragraphs:"]
|
||||
,OrderedList (1,DefaultStyle,DefaultDelim)
|
||||
[[Para [Str "Item",Space,Str "1,",Space,Str "graf",Space,Str "one",Str "."]
|
||||
, Para [Str "Item",Space,Str "1",Str ".",Space,Str "graf",Space,Str "two",Str ".",Space,Str "The",Space,Str "quick",Space,Str "brown",Space,Str "fox",Space,Str "jumped",Space,Str "over",Space,Str "the",Space,Str "lazy",Space,Str "dog",Str "'",Str "s",Space,Str "back",Str "."] ], [ Para [Str "Item",Space,Str "2",Str "."] ]
|
||||
,Para [Str "Item",Space,Str "1",Str ".",Space,Str "graf",Space,Str "two",Str ".",Space,Str "The",Space,Str "quick",Space,Str "brown",Space,Str "fox",Space,Str "jumped",Space,Str "over",Space,Str "the",Space,Str "lazy",Space,Str "dog",Str "'",Str "s",Space,Str "back",Str "."]]
|
||||
,[Para [Str "Item",Space,Str "2",Str "."]]
|
||||
,[Para [Str "Item",Space,Str "3",Str "."]]]
|
||||
,Header 2 [Str "Nested"]
|
||||
,BulletList
|
||||
|
@ -125,8 +122,7 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,BulletList
|
||||
[[Plain [Str "Tab"]
|
||||
,BulletList
|
||||
[ [ Plain [Str "Tab"] ]
|
||||
] ] ] ] ]
|
||||
[[Plain [Str "Tab"]]]]]]]
|
||||
,Para [Str "Here",Str "'",Str "s",Space,Str "another:"]
|
||||
,OrderedList (1,DefaultStyle,DefaultDelim)
|
||||
[[Plain [Str "First"]]
|
||||
|
@ -134,7 +130,8 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,BulletList
|
||||
[[Plain [Str "Fee"]]
|
||||
,[Plain [Str "Fie"]]
|
||||
, [ Plain [Str "Foe"] ] ] ], [ Plain [Str "Third"] ] ]
|
||||
,[Plain [Str "Foe"]]]]
|
||||
,[Plain [Str "Third"]]]
|
||||
,Para [Str "Same",Space,Str "thing",Space,Str "but",Space,Str "with",Space,Str "paragraphs:"]
|
||||
,OrderedList (1,DefaultStyle,DefaultDelim)
|
||||
[[Para [Str "First"]]
|
||||
|
@ -142,7 +139,8 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,BulletList
|
||||
[[Plain [Str "Fee"]]
|
||||
,[Plain [Str "Fie"]]
|
||||
, [ Plain [Str "Foe"] ] ] ], [ Para [Str "Third"] ] ]
|
||||
,[Plain [Str "Foe"]]]]
|
||||
,[Para [Str "Third"]]]
|
||||
,Header 2 [Str "Tabs",Space,Str "and",Space,Str "spaces"]
|
||||
,BulletList
|
||||
[[Para [Str "this",Space,Str "is",Space,Str "a",Space,Str "list",Space,Str "item",Space,Str "indented",Space,Str "with",Space,Str "tabs"]]
|
||||
|
@ -169,25 +167,21 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,OrderedList (6,Decimal,DefaultDelim)
|
||||
[[Plain [Str "Decimal",Space,Str "start",Space,Str "with",Space,Str "6"]
|
||||
,OrderedList (3,LowerAlpha,DefaultDelim)
|
||||
[ [ Plain [Str "Lower",Space,Str "alpha",Space,Str "with",Space,Str "paren"] ]
|
||||
] ] ] ] ] ] ]
|
||||
[[Plain [Str "Lower",Space,Str "alpha",Space,Str "with",Space,Str "paren"]]]]]]]]]
|
||||
,Para [Str "Autonumbering:"]
|
||||
,OrderedList (1,DefaultStyle,DefaultDelim)
|
||||
[[Plain [Str "Autonumber",Str "."]]
|
||||
,[Plain [Str "More",Str "."]
|
||||
,OrderedList (1,DefaultStyle,DefaultDelim)
|
||||
[ [ Plain [Str "Nested",Str "."] ]
|
||||
] ] ]
|
||||
[[Plain [Str "Nested",Str "."]]]]]
|
||||
,HorizontalRule
|
||||
,Header 2 [Str "Definition"]
|
||||
,DefinitionList
|
||||
[([Str "Violin"],
|
||||
[[Plain [Str "Stringed",Space,Str "musical",Space,Str "instrument",Str "."]]
|
||||
, [ Plain [Str "Torture",Space,Str "device",Str "."] ]
|
||||
])
|
||||
,[Plain [Str "Torture",Space,Str "device",Str "."]]])
|
||||
,([Str "Cello",LineBreak,Str "Violoncello"],
|
||||
[ [ Plain [Str "Low",Str "-",Str "voiced",Space,Str "stringed",Space,Str "instrument",Str "."] ]
|
||||
]) ]
|
||||
[[Plain [Str "Low",Str "-",Str "voiced",Space,Str "stringed",Space,Str "instrument",Str "."]]])]
|
||||
,HorizontalRule
|
||||
,Header 1 [Str "HTML",Space,Str "Blocks"]
|
||||
,Para [Str "Simple",Space,Str "block",Space,Str "on",Space,Str "one",Space,Str "line:"]
|
||||
|
@ -328,7 +322,6 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,Plain [Str "An",Space,Str "e",Str "-",Str "mail",Space,Str "address:",Space,Str "nobody",Space,Str "[at]",Space,Str "nowhere",Str ".",Str "net"]
|
||||
,BlockQuote
|
||||
[Para [Str "Blockquoted:",Space,Link [Str "http://example",Str ".",Str "com/"] ("http://example.com/","")]]
|
||||
|
||||
,Para [Str "Auto",Str "-",Str "links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here:",Space,Code "<http://example.com/>"]
|
||||
,CodeBlock ("",[],[]) "or here: <http://example.com/>"
|
||||
,HorizontalRule
|
||||
|
|
|
@ -23,7 +23,6 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,Para [Str "E",Str "-",Str "mail",Space,Str "style:"]
|
||||
,BlockQuote
|
||||
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "block",Space,Str "quote.",Space,Str "It",Space,Str "is",Space,Str "pretty",Space,Str "short."]]
|
||||
|
||||
,BlockQuote
|
||||
[Para [Str "Code",Space,Str "in",Space,Str "a",Space,Str "block",Space,Str "quote:"]
|
||||
,CodeBlock ("",[],[]) "sub status {\n print \"working\";\n}"
|
||||
|
@ -34,10 +33,8 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,Para [Str "Nested",Space,Str "block",Space,Str "quotes:"]
|
||||
,BlockQuote
|
||||
[Para [Str "nested"]]
|
||||
|
||||
,BlockQuote
|
||||
[ Para [Str "nested"] ]
|
||||
]
|
||||
[Para [Str "nested"]]]
|
||||
,Para [Str "This",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "a",Space,Str "block",Space,Str "quote:",Space,Str "2",Space,Str ">",Space,Str "1."]
|
||||
,Para [Str "Box",Str "-",Str "style:"]
|
||||
,BlockQuote
|
||||
|
@ -51,8 +48,7 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,BlockQuote
|
||||
[Para [Str "Joe",Space,Str "said:"]
|
||||
,BlockQuote
|
||||
[ Para [Str "Don",Apostrophe,Str "t",Space,Str "quote",Space,Str "me."] ]
|
||||
]
|
||||
[Para [Str "Don",Apostrophe,Str "t",Space,Str "quote",Space,Str "me."]]]
|
||||
,Para [Str "And",Space,Str "a",Space,Str "following",Space,Str "paragraph."]
|
||||
,HorizontalRule
|
||||
,Header 1 [Str "Code",Space,Str "Blocks"]
|
||||
|
@ -117,7 +113,8 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,Para [Str "Multiple",Space,Str "paragraphs:"]
|
||||
,OrderedList (1,Decimal,Period)
|
||||
[[Para [Str "Item",Space,Str "1,",Space,Str "graf",Space,Str "one."]
|
||||
, Para [Str "Item",Space,Str "1.",Space,Str "graf",Space,Str "two.",Space,Str "The",Space,Str "quick",Space,Str "brown",Space,Str "fox",Space,Str "jumped",Space,Str "over",Space,Str "the",Space,Str "lazy",Space,Str "dog",Apostrophe,Str "s",Space,Str "back."] ], [ Para [Str "Item",Space,Str "2."] ]
|
||||
,Para [Str "Item",Space,Str "1.",Space,Str "graf",Space,Str "two.",Space,Str "The",Space,Str "quick",Space,Str "brown",Space,Str "fox",Space,Str "jumped",Space,Str "over",Space,Str "the",Space,Str "lazy",Space,Str "dog",Apostrophe,Str "s",Space,Str "back."]]
|
||||
,[Para [Str "Item",Space,Str "2."]]
|
||||
,[Para [Str "Item",Space,Str "3."]]]
|
||||
,Header 2 [Str "Nested"]
|
||||
,BulletList
|
||||
|
@ -125,8 +122,7 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,BulletList
|
||||
[[Para [Str "Tab"]
|
||||
,BulletList
|
||||
[ [ Para [Str "Tab"] ]
|
||||
] ] ] ] ]
|
||||
[[Para [Str "Tab"]]]]]]]
|
||||
,Para [Str "Here",Apostrophe,Str "s",Space,Str "another:"]
|
||||
,OrderedList (1,Decimal,Period)
|
||||
[[Para [Str "First"]]
|
||||
|
@ -134,7 +130,8 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,BulletList
|
||||
[[Para [Str "Fee"]]
|
||||
,[Para [Str "Fie"]]
|
||||
, [ Para [Str "Foe"] ] ] ], [ Para [Str "Third"] ] ]
|
||||
,[Para [Str "Foe"]]]]
|
||||
,[Para [Str "Third"]]]
|
||||
,Para [Str "Same",Space,Str "thing",Space,Str "but",Space,Str "with",Space,Str "paragraphs:"]
|
||||
,OrderedList (1,Decimal,Period)
|
||||
[[Para [Str "First"]]
|
||||
|
@ -142,7 +139,8 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,BulletList
|
||||
[[Para [Str "Fee"]]
|
||||
,[Para [Str "Fie"]]
|
||||
, [ Para [Str "Foe"] ] ] ], [ Para [Str "Third"] ] ]
|
||||
,[Para [Str "Foe"]]]]
|
||||
,[Para [Str "Third"]]]
|
||||
,Header 2 [Str "Tabs",Space,Str "and",Space,Str "spaces"]
|
||||
,BulletList
|
||||
[[Para [Str "this",Space,Str "is",Space,Str "a",Space,Str "list",Space,Str "item",Space,Str "indented",Space,Str "with",Space,Str "tabs"]]
|
||||
|
@ -169,15 +167,13 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,OrderedList (6,Decimal,TwoParens)
|
||||
[[Para [Str "Decimal",Space,Str "start",Space,Str "with",Space,Str "6"]
|
||||
,OrderedList (3,LowerAlpha,OneParen)
|
||||
[ [ Para [Str "Lower",Space,Str "alpha",Space,Str "with",Space,Str "paren"] ]
|
||||
] ] ] ] ] ] ]
|
||||
[[Para [Str "Lower",Space,Str "alpha",Space,Str "with",Space,Str "paren"]]]]]]]]]
|
||||
,Para [Str "Autonumbering:"]
|
||||
,OrderedList (1,DefaultStyle,DefaultDelim)
|
||||
[[Para [Str "Autonumber."]]
|
||||
,[Para [Str "More."]
|
||||
,OrderedList (1,DefaultStyle,DefaultDelim)
|
||||
[ [ Para [Str "Nested."] ]
|
||||
] ] ]
|
||||
[[Para [Str "Nested."]]]]]
|
||||
,Para [Str "Should",Space,Str "not",Space,Str "be",Space,Str "a",Space,Str "list",Space,Str "item:"]
|
||||
,Para [Str "M.A.",Space,Str "2007"]
|
||||
,Para [Str "B.",Space,Str "Williams"]
|
||||
|
@ -186,36 +182,27 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,Para [Str "Tight",Space,Str "using",Space,Str "spaces:"]
|
||||
,DefinitionList
|
||||
[([Str "apple"],
|
||||
[ [ Para [Str "red",Space,Str "fruit"] ]
|
||||
])
|
||||
[[Para [Str "red",Space,Str "fruit"]]])
|
||||
,([Str "orange"],
|
||||
[ [ Para [Str "orange",Space,Str "fruit"] ]
|
||||
])
|
||||
[[Para [Str "orange",Space,Str "fruit"]]])
|
||||
,([Str "banana"],
|
||||
[ [ Para [Str "yellow",Space,Str "fruit"] ]
|
||||
]) ]
|
||||
[[Para [Str "yellow",Space,Str "fruit"]]])]
|
||||
,Para [Str "Tight",Space,Str "using",Space,Str "tabs:"]
|
||||
,DefinitionList
|
||||
[([Str "apple"],
|
||||
[ [ Para [Str "red",Space,Str "fruit"] ]
|
||||
])
|
||||
[[Para [Str "red",Space,Str "fruit"]]])
|
||||
,([Str "orange"],
|
||||
[ [ Para [Str "orange",Space,Str "fruit"] ]
|
||||
])
|
||||
[[Para [Str "orange",Space,Str "fruit"]]])
|
||||
,([Str "banana"],
|
||||
[ [ Para [Str "yellow",Space,Str "fruit"] ]
|
||||
]) ]
|
||||
[[Para [Str "yellow",Space,Str "fruit"]]])]
|
||||
,Para [Str "Loose:"]
|
||||
,DefinitionList
|
||||
[([Str "apple"],
|
||||
[ [ Para [Str "red",Space,Str "fruit"] ]
|
||||
])
|
||||
[[Para [Str "red",Space,Str "fruit"]]])
|
||||
,([Str "orange"],
|
||||
[ [ Para [Str "orange",Space,Str "fruit"] ]
|
||||
])
|
||||
[[Para [Str "orange",Space,Str "fruit"]]])
|
||||
,([Str "banana"],
|
||||
[ [ Para [Str "yellow",Space,Str "fruit"] ]
|
||||
]) ]
|
||||
[[Para [Str "yellow",Space,Str "fruit"]]])]
|
||||
,Para [Str "Multiple",Space,Str "blocks",Space,Str "with",Space,Str "italics:"]
|
||||
,DefinitionList
|
||||
[([Emph [Str "apple"]],
|
||||
|
@ -225,8 +212,7 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
[[Para [Str "orange",Space,Str "fruit"]
|
||||
,CodeBlock ("",[],[]) "{ orange code block }"
|
||||
,BlockQuote
|
||||
[ Para [Str "orange",Space,Str "block",Space,Str "quote"] ]
|
||||
]]) ]
|
||||
[Para [Str "orange",Space,Str "block",Space,Str "quote"]]]])]
|
||||
,Header 1 [Str "HTML",Space,Str "Blocks"]
|
||||
,Para [Str "Simple",Space,Str "block",Space,Str "on",Space,Str "one",Space,Str "line:"]
|
||||
,Para [Str "foo",Space,Str "And",Space,Str "nested",Space,Str "without",Space,Str "indentation:"]
|
||||
|
@ -289,10 +275,10 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,Para [Str "Here",Apostrophe,Str "s",Space,Str "a",Space,Str "LaTeX",Space,Str "table:"]
|
||||
,Table [] [AlignLeft,AlignLeft] [0.0,0.0]
|
||||
[[Plain [Str "Animal"]]
|
||||
, [ Plain [Str "Number"] ] ] [
|
||||
[ [ Plain [Str "Dog"] ]
|
||||
, [ Plain [Str "2"] ] ],
|
||||
[ [ Plain [Str "Cat"] ]
|
||||
,[Plain [Str "Number"]]]
|
||||
[[[Plain [Str "Dog"]]
|
||||
,[Plain [Str "2"]]]
|
||||
,[[Plain [Str "Cat"]]
|
||||
,[Plain [Str "1"]]]]
|
||||
,HorizontalRule
|
||||
,Header 1 [Str "Special",Space,Str "Characters"]
|
||||
|
@ -363,7 +349,6 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,Para [Str "An",Space,Str "e",Str "-",Str "mail",Space,Str "address:",Space,Link [Code "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")]
|
||||
,BlockQuote
|
||||
[Para [Str "Blockquoted:",Space,Link [Code "http://example.com/"] ("http://example.com/","")]]
|
||||
|
||||
,Para [Str "Auto",Str "-",Str "links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here:",Space,Code "<http://example.com/>"]
|
||||
,CodeBlock ("",[],[]) "or here: <http://example.com/>"
|
||||
,HorizontalRule
|
||||
|
@ -376,8 +361,6 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Note [Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote.",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "after",Space,Str "the",Space,Str "footnote",Space,Str "reference.",Space,Str "It",Space,Str "need",Space,Str "not",Space,Str "be",Space,Str "placed",Space,Str "at",Space,Str "the",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "document."]],Space,Str "and",Space,Str "another.",Note [Para [Str "Here",Apostrophe,Str "s",Space,Str "the",Space,Str "long",Space,Str "note.",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks."],Para [Str "Subsequent",Space,Str "blocks",Space,Str "are",Space,Str "indented",Space,Str "to",Space,Str "show",Space,Str "that",Space,Str "they",Space,Str "belong",Space,Str "to",Space,Str "the",Space,Str "footnote",Space,Str "(as",Space,Str "with",Space,Str "list",Space,Str "items)."],CodeBlock ("",[],[]) " { <code> }",Para [Str "If",Space,Str "you",Space,Str "want,",Space,Str "you",Space,Str "can",Space,Str "indent",Space,Str "every",Space,Str "line,",Space,Str "but",Space,Str "you",Space,Str "can",Space,Str "also",Space,Str "be",Space,Str "lazy",Space,Str "and",Space,Str "just",Space,Str "indent",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "each",Space,Str "block."]],Space,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Space,Str "because",Space,Str "it",Space,Str "contains",Space,Str "a",Space,Str "space.",Str "[",Str "^",Str "my",Space,Str "note",Str "]",Space,Str "Here",Space,Str "is",Space,Str "an",Space,Str "inline",Space,Str "note.",Note [Para [Str "This",Space,Str "is",Space,Emph [Str "easier"],Space,Str "to",Space,Str "type.",Space,Str "Inline",Space,Str "notes",Space,Str "may",Space,Str "contain",Space,Link [Str "links"] ("http://google.com",""),Space,Str "and",Space,Code "]",Space,Str "verbatim",Space,Str "characters,",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "[",Str "bracketed",Space,Str "text",Str "]",Str "."]]]
|
||||
,BlockQuote
|
||||
[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)
|
||||
[ [ Para [Str "And",Space,Str "in",Space,Str "list",Space,Str "items.",Note [Para [Str "In",Space,Str "list."]]] ]
|
||||
]
|
||||
[[Para [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."]]
|
|
@ -18,4 +18,3 @@ second item of the pair).
|
|||
Block quote:
|
||||
|
||||
> foo bar
|
||||
|
||||
|
|
|
@ -17,4 +17,3 @@ second item of the pair).
|
|||
Block quote:
|
||||
|
||||
> foo bar
|
||||
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
||||
[Header 1 [Str "lhs",Space,Str "test"]
|
||||
,Para [Code "unsplit",Space,Str "is",Space,Str "an",Space,Str "arrow",Space,Str "that",Space,Str "takes",Space,Str "a",Space,Str "pair",Space,Str "of",Space,Str "values",Space,Str "and",Space,Str "combines",Space,Str "them",Space,Str "to",Space,Str "return",Space,Str "a",Space,Str "single",Space,Str "value",Str ":"]
|
||||
,CodeBlock ("",["sourceCode","literate","haskell"],[]) "unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d\nunsplit = arr . uncurry \n -- arr (\\op (x,y) -> x `op` y) "
|
||||
|
@ -6,5 +5,4 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
|||
,CodeBlock ("",[],[]) "f *** g = first f >>> second g"
|
||||
,Para [Str "Block",Space,Str "quote",Str ":"]
|
||||
,BlockQuote
|
||||
[ Para [Str "foo",Space,Str "bar"] ]
|
||||
]
|
||||
[Para [Str "foo",Space,Str "bar"]]]
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
Pandoc (Meta {docTitle = [Str "Title",Space,Str "spanning",Space,Str "multiple",Space,Str "lines"], docAuthors = [[Str "Author",Space,Str "One"],[Str "Author",Space,Str "Two"],[Str "Author",Space,Str "Three"],[Str "Author",Space,Str "Four"]], docDate = []})
|
||||
[Header 1 [Str "Additional",Space,Str "markdown",Space,Str "reader",Space,Str "tests"]
|
||||
,Header 2 [Str "Blank",Space,Str "line",Space,Str "before",Space,Str "URL",Space,Str "in",Space,Str "link",Space,Str "reference"]
|
||||
,Para [Link [Str "foo"] ("/url",""),Space,Str "and",Space,Link [Str "bar"] ("/url","title")]
|
||||
|
@ -38,8 +37,7 @@ Pandoc (Meta {docTitle = [Str "Title",Space,Str "spanning",Space,Str "multiple",
|
|||
,[Plain [Str "Second",Space,Str "example",Str "."]]]
|
||||
,Para [Str "Explanation",Space,Str "of",Space,Str "examples",Space,Str "(",Str "2",Str ")",Space,Str "and",Space,Str "(",Str "3",Str ")",Str "."]
|
||||
,OrderedList (3,Example,TwoParens)
|
||||
[ [ Plain [Str "Third",Space,Str "example",Str "."] ]
|
||||
]
|
||||
[[Plain [Str "Third",Space,Str "example",Str "."]]]
|
||||
,Header 2 [Str "Macros"]
|
||||
,Para [Math InlineMath "\\langle x,y \\rangle"]
|
||||
,Header 2 [Str "Case",Str "-",Str "insensitive",Space,Str "references"]
|
||||
|
@ -49,4 +47,3 @@ Pandoc (Meta {docTitle = [Str "Title",Space,Str "spanning",Space,Str "multiple",
|
|||
,Header 2 [Str "Curly",Space,Str "smart",Space,Str "quotes"]
|
||||
,Para [Quoted DoubleQuote [Str "Hi"]]
|
||||
,Para [Quoted SingleQuote [Str "Hi"]]]
|
||||
|
||||
|
|
|
@ -1,8 +1,7 @@
|
|||
Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite",Str ":",Space,Str "Subtitle"], docAuthors = [[Str "John",Space,Str "MacFarlane"],[Str "Anonymous"]], docDate = [Str "July",Space,Str "17,",Space,Str "2006"]})
|
||||
[DefinitionList
|
||||
[([Str "Revision"],
|
||||
[ [ Plain [Str "3"] ]
|
||||
]) ]
|
||||
[[Plain [Str "3"]]])]
|
||||
,Header 1 [Str "Level",Space,Str "one",Space,Str "header"]
|
||||
,Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc",Str ".",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber",Apostrophe,Str "s",Space,Str "markdown",Space,Str "test",Space,Str "suite",Str "."]
|
||||
,Header 2 [Str "Level",Space,Str "two",Space,Str "header"]
|
||||
|
@ -21,7 +20,6 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite",Str ":
|
|||
,Para [Str "Here",Apostrophe,Str "s",Space,Str "a",Space,Str "block",Space,Str "quote",Str ":"]
|
||||
,BlockQuote
|
||||
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "block",Space,Str "quote",Str ".",Space,Str "It",Space,Str "is",Space,Str "pretty",Space,Str "short",Str "."]]
|
||||
|
||||
,Para [Str "Here",Apostrophe,Str "s",Space,Str "another,",Space,Str "differently",Space,Str "indented",Str ":"]
|
||||
,BlockQuote
|
||||
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "block",Space,Str "quote",Str ".",Space,Str "It",Apostrophe,Str "s",Space,Str "indented",Space,Str "with",Space,Str "a",Space,Str "tab",Str "."]
|
||||
|
@ -35,8 +33,7 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite",Str ":
|
|||
,BlockQuote
|
||||
[Para [Str "nested"]
|
||||
,BlockQuote
|
||||
[ Para [Str "nested"] ]
|
||||
] ]
|
||||
[Para [Str "nested"]]]]
|
||||
,Header 1 [Str "Code",Space,Str "Blocks"]
|
||||
,Para [Str "Code",Str ":"]
|
||||
,CodeBlock ("",[],[]) "---- (should be four hyphens)\n\nsub status {\n print \"working\";\n}"
|
||||
|
@ -101,7 +98,8 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite",Str ":
|
|||
,Para [Str "Multiple",Space,Str "paragraphs",Str ":"]
|
||||
,OrderedList (1,Decimal,Period)
|
||||
[[Para [Str "Item",Space,Str "1,",Space,Str "graf",Space,Str "one",Str "."]
|
||||
, Para [Str "Item",Space,Str "1",Str ".",Space,Str "graf",Space,Str "two",Str ".",Space,Str "The",Space,Str "quick",Space,Str "brown",Space,Str "fox",Space,Str "jumped",Space,Str "over",Space,Str "the",Space,Str "lazy",Space,Str "dog",Apostrophe,Str "s",Space,Str "back",Str "."] ], [ Para [Str "Item",Space,Str "2",Str "."] ]
|
||||
,Para [Str "Item",Space,Str "1",Str ".",Space,Str "graf",Space,Str "two",Str ".",Space,Str "The",Space,Str "quick",Space,Str "brown",Space,Str "fox",Space,Str "jumped",Space,Str "over",Space,Str "the",Space,Str "lazy",Space,Str "dog",Apostrophe,Str "s",Space,Str "back",Str "."]]
|
||||
,[Para [Str "Item",Space,Str "2",Str "."]]
|
||||
,[Para [Str "Item",Space,Str "3",Str "."]]]
|
||||
,Para [Str "Nested",Str ":"]
|
||||
,BulletList
|
||||
|
@ -109,8 +107,7 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite",Str ":
|
|||
,BulletList
|
||||
[[Para [Str "Tab"]
|
||||
,BulletList
|
||||
[ [ Plain [Str "Tab"] ]
|
||||
] ] ] ] ]
|
||||
[[Plain [Str "Tab"]]]]]]]
|
||||
,Para [Str "Here",Apostrophe,Str "s",Space,Str "another",Str ":"]
|
||||
,OrderedList (1,Decimal,Period)
|
||||
[[Para [Str "First"]]
|
||||
|
@ -119,7 +116,8 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite",Str ":
|
|||
[BulletList
|
||||
[[Plain [Str "Fee"]]
|
||||
,[Plain [Str "Fie"]]
|
||||
, [ Plain [Str "Foe"] ] ] ] ], [ Para [Str "Third"] ] ]
|
||||
,[Plain [Str "Foe"]]]]]
|
||||
,[Para [Str "Third"]]]
|
||||
,Header 2 [Str "Fancy",Space,Str "list",Space,Str "markers"]
|
||||
,OrderedList (2,Decimal,TwoParens)
|
||||
[[Plain [Str "begins",Space,Str "with",Space,Str "2"]]
|
||||
|
@ -139,15 +137,13 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite",Str ":
|
|||
,OrderedList (6,Decimal,TwoParens)
|
||||
[[Para [Str "Decimal",Space,Str "start",Space,Str "with",Space,Str "6"]
|
||||
,OrderedList (3,LowerAlpha,OneParen)
|
||||
[ [ Plain [Str "Lower",Space,Str "alpha",Space,Str "with",Space,Str "paren"] ]
|
||||
] ] ] ] ] ] ]
|
||||
[[Plain [Str "Lower",Space,Str "alpha",Space,Str "with",Space,Str "paren"]]]]]]]]]
|
||||
,Para [Str "Autonumbering",Str ":"]
|
||||
,OrderedList (1,DefaultStyle,DefaultDelim)
|
||||
[[Plain [Str "Autonumber",Str "."]]
|
||||
,[Para [Str "More",Str "."]
|
||||
,OrderedList (1,DefaultStyle,DefaultDelim)
|
||||
[ [ Plain [Str "Nested",Str "."] ]
|
||||
] ] ]
|
||||
[[Plain [Str "Nested",Str "."]]]]]
|
||||
,Para [Str "Autonumbering",Space,Str "with",Space,Str "explicit",Space,Str "start",Str ":"]
|
||||
,OrderedList (4,LowerAlpha,TwoParens)
|
||||
[[Plain [Str "item",Space,Str "1"]]
|
||||
|
@ -155,35 +151,27 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite",Str ":
|
|||
,Header 2 [Str "Definition"]
|
||||
,DefinitionList
|
||||
[([Str "term",Space,Str "1"],
|
||||
[ [ Para [Str "Definition",Space,Str "1",Str "."] ]
|
||||
])
|
||||
[[Para [Str "Definition",Space,Str "1",Str "."]]])
|
||||
,([Str "term",Space,Str "2"],
|
||||
[[Para [Str "Definition",Space,Str "2,",Space,Str "paragraph",Space,Str "1",Str "."]
|
||||
,Para [Str "Definition",Space,Str "2,",Space,Str "paragraph",Space,Str "2",Str "."]]])
|
||||
,([Str "term",Space,Str "with",Space,Emph [Str "emphasis"]],
|
||||
[ [ Para [Str "Definition",Space,Str "3",Str "."] ]
|
||||
]) ]
|
||||
[[Para [Str "Definition",Space,Str "3",Str "."]]])]
|
||||
,Header 1 [Str "Field",Space,Str "Lists"]
|
||||
,DefinitionList
|
||||
[([Str "address"],
|
||||
[ [ Plain [Str "61",Space,Str "Main",Space,Str "St",Str "."] ]
|
||||
])
|
||||
[[Plain [Str "61",Space,Str "Main",Space,Str "St",Str "."]]])
|
||||
,([Str "city"],
|
||||
[ [ Plain [Emph [Str "Nowhere"],Str ",",Space,Str "MA,",Space,Str "USA"] ]
|
||||
])
|
||||
[[Plain [Emph [Str "Nowhere"],Str ",",Space,Str "MA,",Space,Str "USA"]]])
|
||||
,([Str "phone"],
|
||||
[ [ Plain [Str "123",EnDash,Str "4567"] ]
|
||||
]) ]
|
||||
[[Plain [Str "123",EnDash,Str "4567"]]])]
|
||||
,DefinitionList
|
||||
[([Str "address"],
|
||||
[ [ Plain [Str "61",Space,Str "Main",Space,Str "St",Str "."] ]
|
||||
])
|
||||
[[Plain [Str "61",Space,Str "Main",Space,Str "St",Str "."]]])
|
||||
,([Str "city"],
|
||||
[ [ Plain [Emph [Str "Nowhere"],Str ",",Space,Str "MA,",Space,Str "USA"] ]
|
||||
])
|
||||
[[Plain [Emph [Str "Nowhere"],Str ",",Space,Str "MA,",Space,Str "USA"]]])
|
||||
,([Str "phone"],
|
||||
[ [ Plain [Str "123",EnDash,Str "4567"] ]
|
||||
]) ]
|
||||
[[Plain [Str "123",EnDash,Str "4567"]]])]
|
||||
,Header 1 [Str "HTML",Space,Str "Blocks"]
|
||||
,Para [Str "Simple",Space,Str "block",Space,Str "on",Space,Str "one",Space,Str "line",Str ":"]
|
||||
,RawHtml "<div>foo</div>\n"
|
||||
|
@ -248,67 +236,69 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite",Str ":
|
|||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[[Plain [Str "col",Space,Str "1"]]
|
||||
,[Plain [Str "col",Space,Str "2"]]
|
||||
, [ Plain [Str "col",Space,Str "3"] ] ] [
|
||||
[ [ Plain [Str "r1",Space,Str "a"] ]
|
||||
,[Plain [Str "col",Space,Str "3"]]]
|
||||
[[[Plain [Str "r1",Space,Str "a"]]
|
||||
,[Plain [Str "b"]]
|
||||
, [ Plain [Str "c"] ] ],
|
||||
[ [ Plain [Str "r2",Space,Str "d"] ]
|
||||
,[Plain [Str "c"]]]
|
||||
,[[Plain [Str "r2",Space,Str "d"]]
|
||||
,[Plain [Str "e"]]
|
||||
,[Plain [Str "f"]]]]
|
||||
,Para [Str "Headless"]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[[]
|
||||
,[]
|
||||
, [] ] [
|
||||
[ [ Plain [Str "r1",Space,Str "a"] ]
|
||||
,[]]
|
||||
[[[Plain [Str "r1",Space,Str "a"]]
|
||||
,[Plain [Str "b"]]
|
||||
, [ Plain [Str "c"] ] ],
|
||||
[ [ Plain [Str "r2",Space,Str "d"] ]
|
||||
,[Plain [Str "c"]]]
|
||||
,[[Plain [Str "r2",Space,Str "d"]]
|
||||
,[Plain [Str "e"]]
|
||||
,[Plain [Str "f"]]]]
|
||||
,Header 1 [Str "Grid",Space,Str "Tables"]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.2375,0.15,0.1625]
|
||||
[[Plain [Str "col",Space,Str "1"]]
|
||||
,[Plain [Str "col",Space,Str "2"]]
|
||||
, [ Plain [Str "col",Space,Str "3"] ] ] [
|
||||
[ [ Plain [Str "r1",Space,Str "a",Space,Str "r1",Space,Str "bis"] ]
|
||||
,[Plain [Str "col",Space,Str "3"]]]
|
||||
[[[Plain [Str "r1",Space,Str "a",Space,Str "r1",Space,Str "bis"]]
|
||||
,[Plain [Str "b",Space,Str "b",Space,Str "2"]]
|
||||
, [ Plain [Str "c",Space,Str "c",Space,Str "2"] ] ],
|
||||
[ [ Plain [Str "r2",Space,Str "d"] ]
|
||||
,[Plain [Str "c",Space,Str "c",Space,Str "2"]]]
|
||||
,[[Plain [Str "r2",Space,Str "d"]]
|
||||
,[Plain [Str "e"]]
|
||||
,[Plain [Str "f"]]]]
|
||||
,Para [Str "Headless"]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.2375,0.15,0.1625]
|
||||
[[]
|
||||
,[]
|
||||
, [] ] [
|
||||
[ [ Plain [Str "r1",Space,Str "a",Space,Str "r1",Space,Str "bis"] ]
|
||||
,[]]
|
||||
[[[Plain [Str "r1",Space,Str "a",Space,Str "r1",Space,Str "bis"]]
|
||||
,[Plain [Str "b",Space,Str "b",Space,Str "2"]]
|
||||
, [ Plain [Str "c",Space,Str "c",Space,Str "2"] ] ],
|
||||
[ [ Plain [Str "r2",Space,Str "d"] ]
|
||||
,[Plain [Str "c",Space,Str "c",Space,Str "2"]]]
|
||||
,[[Plain [Str "r2",Space,Str "d"]]
|
||||
,[Plain [Str "e"]]
|
||||
,[Plain [Str "f"]]]]
|
||||
,Para [Str "Spaces",Space,Str "at",Space,Str "ends",Space,Str "of",Space,Str "lines"]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.2375,0.15,0.1625]
|
||||
[[]
|
||||
,[]
|
||||
, [] ] [
|
||||
[ [ Plain [Str "r1",Space,Str "a",Space,Str "r1",Space,Str "bis"] ]
|
||||
,[]]
|
||||
[[[Plain [Str "r1",Space,Str "a",Space,Str "r1",Space,Str "bis"]]
|
||||
,[Plain [Str "b",Space,Str "b",Space,Str "2"]]
|
||||
, [ Plain [Str "c",Space,Str "c",Space,Str "2"] ] ],
|
||||
[ [ Plain [Str "r2",Space,Str "d"] ]
|
||||
,[Plain [Str "c",Space,Str "c",Space,Str "2"]]]
|
||||
,[[Plain [Str "r2",Space,Str "d"]]
|
||||
,[Plain [Str "e"]]
|
||||
,[Plain [Str "f"]]]]
|
||||
,Para [Str "Multiple",Space,Str "blocks",Space,Str "in",Space,Str "a",Space,Str "cell"]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.2375,0.15,0.1625]
|
||||
[[]
|
||||
,[]
|
||||
, [] ] [
|
||||
[ [ Para [Str "r1",Space,Str "a"]
|
||||
, Para [Str "r1",Space,Str "bis"] ], [ BulletList
|
||||
,[]]
|
||||
[[[Para [Str "r1",Space,Str "a"]
|
||||
,Para [Str "r1",Space,Str "bis"]]
|
||||
,[BulletList
|
||||
[[Plain [Str "b"]]
|
||||
,[Plain [Str "b",Space,Str "2"]]
|
||||
, [ Plain [Str "b",Space,Str "2"] ] ] ], [ Plain [Str "c",Space,Str "c",Space,Str "2",Space,Str "c",Space,Str "2"] ] ] ]
|
||||
,[Plain [Str "b",Space,Str "2"]]]]
|
||||
,[Plain [Str "c",Space,Str "c",Space,Str "2",Space,Str "c",Space,Str "2"]]]]
|
||||
,Header 1 [Str "Footnotes"]
|
||||
,Para [Note [Para [Str "Note",Space,Str "with",Space,Str "one",Space,Str "line",Str "."]]]
|
||||
,Para [Note [Para [Str "Note",Space,Str "with",Space,Str "continuation",Space,Str "line",Str "."]]]
|
||||
|
|
|
@ -5,5 +5,4 @@ Pandoc (Meta {docTitle = [Str "My",Space,Str "S5",Space,Str "Document"], docAuth
|
|||
,[Plain [Str "second",Space,Str "bullet"]]]
|
||||
,Header 1 [Str "Math"]
|
||||
,BulletList
|
||||
[ [ Plain [Math InlineMath "\\frac{d}{dx}f(x)=\\lim_{h\\to 0}\\frac{f(x+h)-f(x)}{h}"] ]
|
||||
] ]
|
||||
[[Plain [Math InlineMath "\\frac{d}{dx}f(x)=\\lim_{h\\to 0}\\frac{f(x+h)-f(x)}{h}"]]]]
|
|
@ -1,19 +1,18 @@
|
|||
Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
||||
[Para [Str "Simple",Space,Str "table",Space,Str "with",Space,Str "caption",Str ":"]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.125,0.1125,0.1375,0.15]
|
||||
[[Plain [Str "Right"]]
|
||||
,[Plain [Str "Left"]]
|
||||
,[Plain [Str "Center"]]
|
||||
, [ Plain [Str "Default"] ] ] [
|
||||
[ [ Plain [Str "12"] ]
|
||||
,[Plain [Str "Default"]]]
|
||||
[[[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
, [ Plain [Str "12"] ] ],
|
||||
[ [ Plain [Str "123"] ]
|
||||
,[Plain [Str "12"]]]
|
||||
,[[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
, [ Plain [Str "123"] ] ],
|
||||
[ [ Plain [Str "1"] ]
|
||||
,[Plain [Str "123"]]]
|
||||
,[[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]]]
|
||||
|
@ -23,16 +22,16 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
|||
[[Plain [Str "Right"]]
|
||||
,[Plain [Str "Left"]]
|
||||
,[Plain [Str "Center"]]
|
||||
, [ Plain [Str "Default"] ] ] [
|
||||
[ [ Plain [Str "12"] ]
|
||||
,[Plain [Str "Default"]]]
|
||||
[[[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
, [ Plain [Str "12"] ] ],
|
||||
[ [ Plain [Str "123"] ]
|
||||
,[Plain [Str "12"]]]
|
||||
,[[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
, [ Plain [Str "123"] ] ],
|
||||
[ [ Plain [Str "1"] ]
|
||||
,[Plain [Str "123"]]]
|
||||
,[[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]]]
|
||||
|
@ -41,16 +40,16 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
|||
[[Plain [Str "Right"]]
|
||||
,[Plain [Str "Left"]]
|
||||
,[Plain [Str "Center"]]
|
||||
, [ Plain [Str "Default"] ] ] [
|
||||
[ [ Plain [Str "12"] ]
|
||||
,[Plain [Str "Default"]]]
|
||||
[[[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
, [ Plain [Str "12"] ] ],
|
||||
[ [ Plain [Str "123"] ]
|
||||
,[Plain [Str "12"]]]
|
||||
,[[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
, [ Plain [Str "123"] ] ],
|
||||
[ [ Plain [Str "1"] ]
|
||||
,[Plain [Str "123"]]]
|
||||
,[[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]]]
|
||||
|
@ -60,12 +59,12 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
|||
[[Plain [Str "Centered",Space,Str "Header"]]
|
||||
,[Plain [Str "Left",Space,Str "Aligned"]]
|
||||
,[Plain [Str "Right",Space,Str "Aligned"]]
|
||||
, [ Plain [Str "Default",Space,Str "aligned"] ] ] [
|
||||
[ [ Plain [Str "First"] ]
|
||||
,[Plain [Str "Default",Space,Str "aligned"]]]
|
||||
[[[Plain [Str "First"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "12",Str ".",Str "0"]]
|
||||
, [ Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines",Str "."] ] ],
|
||||
[ [ Plain [Str "Second"] ]
|
||||
,[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines",Str "."]]]
|
||||
,[[Plain [Str "Second"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "5",Str ".",Str "0"]]
|
||||
,[Plain [Str "Here",Str "'",Str "s",Space,Str "another",Space,Str "one",Str ".",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows",Str "."]]]]
|
||||
|
@ -75,12 +74,12 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
|||
[[Plain [Str "Centered",Space,Str "Header"]]
|
||||
,[Plain [Str "Left",Space,Str "Aligned"]]
|
||||
,[Plain [Str "Right",Space,Str "Aligned"]]
|
||||
, [ Plain [Str "Default",Space,Str "aligned"] ] ] [
|
||||
[ [ Plain [Str "First"] ]
|
||||
,[Plain [Str "Default",Space,Str "aligned"]]]
|
||||
[[[Plain [Str "First"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "12",Str ".",Str "0"]]
|
||||
, [ Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines",Str "."] ] ],
|
||||
[ [ Plain [Str "Second"] ]
|
||||
,[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines",Str "."]]]
|
||||
,[[Plain [Str "Second"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "5",Str ".",Str "0"]]
|
||||
,[Plain [Str "Here",Str "'",Str "s",Space,Str "another",Space,Str "one",Str ".",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows",Str "."]]]]
|
||||
|
@ -89,16 +88,16 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
|||
[[]
|
||||
,[]
|
||||
,[]
|
||||
, [] ] [
|
||||
[ [ Plain [Str "12"] ]
|
||||
,[]]
|
||||
[[[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
, [ Plain [Str "12"] ] ],
|
||||
[ [ Plain [Str "123"] ]
|
||||
,[Plain [Str "12"]]]
|
||||
,[[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
, [ Plain [Str "123"] ] ],
|
||||
[ [ Plain [Str "1"] ]
|
||||
,[Plain [Str "123"]]]
|
||||
,[[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]]]
|
||||
|
@ -107,13 +106,12 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
|||
[[]
|
||||
,[]
|
||||
,[]
|
||||
, [] ] [
|
||||
[ [ Plain [Str "First"] ]
|
||||
,[]]
|
||||
[[[Plain [Str "First"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "12",Str ".",Str "0"]]
|
||||
, [ Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines",Str "."] ] ],
|
||||
[ [ Plain [Str "Second"] ]
|
||||
,[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines",Str "."]]]
|
||||
,[[Plain [Str "Second"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "5",Str ".",Str "0"]]
|
||||
,[Plain [Str "Here",Str "'",Str "s",Space,Str "another",Space,Str "one",Str ".",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows",Str "."]]]]]
|
||||
|
||||
|
|
|
@ -1,19 +1,18 @@
|
|||
Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
||||
[Para [Str "Simple",Space,Str "table",Space,Str "with",Space,Str "caption",Str ":"]
|
||||
,Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax",Str "."] [AlignRight,AlignLeft,AlignCenter,AlignDefault] [0.0,0.0,0.0,0.0]
|
||||
[[Plain [Str "Right"]]
|
||||
,[Plain [Str "Left"]]
|
||||
,[Plain [Str "Center"]]
|
||||
, [ Plain [Str "Default"] ] ] [
|
||||
[ [ Plain [Str "12"] ]
|
||||
,[Plain [Str "Default"]]]
|
||||
[[[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
, [ Plain [Str "12"] ] ],
|
||||
[ [ Plain [Str "123"] ]
|
||||
,[Plain [Str "12"]]]
|
||||
,[[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
, [ Plain [Str "123"] ] ],
|
||||
[ [ Plain [Str "1"] ]
|
||||
,[Plain [Str "123"]]]
|
||||
,[[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]]]
|
||||
|
@ -22,16 +21,16 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
|||
[[Plain [Str "Right"]]
|
||||
,[Plain [Str "Left"]]
|
||||
,[Plain [Str "Center"]]
|
||||
, [ Plain [Str "Default"] ] ] [
|
||||
[ [ Plain [Str "12"] ]
|
||||
,[Plain [Str "Default"]]]
|
||||
[[[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
, [ Plain [Str "12"] ] ],
|
||||
[ [ Plain [Str "123"] ]
|
||||
,[Plain [Str "12"]]]
|
||||
,[[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
, [ Plain [Str "123"] ] ],
|
||||
[ [ Plain [Str "1"] ]
|
||||
,[Plain [Str "123"]]]
|
||||
,[[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]]]
|
||||
|
@ -40,16 +39,16 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
|||
[[Plain [Str "Right"]]
|
||||
,[Plain [Str "Left"]]
|
||||
,[Plain [Str "Center"]]
|
||||
, [ Plain [Str "Default"] ] ] [
|
||||
[ [ Plain [Str "12"] ]
|
||||
,[Plain [Str "Default"]]]
|
||||
[[[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
, [ Plain [Str "12"] ] ],
|
||||
[ [ Plain [Str "123"] ]
|
||||
,[Plain [Str "12"]]]
|
||||
,[[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
, [ Plain [Str "123"] ] ],
|
||||
[ [ Plain [Str "1"] ]
|
||||
,[Plain [Str "123"]]]
|
||||
,[[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]]]
|
||||
|
@ -58,12 +57,12 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
|||
[[Plain [Str "Centered",Space,Str "Header"]]
|
||||
,[Plain [Str "Left",Space,Str "Aligned"]]
|
||||
,[Plain [Str "Right",Space,Str "Aligned"]]
|
||||
, [ Plain [Str "Default",Space,Str "aligned"] ] ] [
|
||||
[ [ Plain [Str "First"] ]
|
||||
,[Plain [Str "Default",Space,Str "aligned"]]]
|
||||
[[[Plain [Str "First"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "12",Str ".",Str "0"]]
|
||||
, [ Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines",Str "."] ] ],
|
||||
[ [ Plain [Str "Second"] ]
|
||||
,[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines",Str "."]]]
|
||||
,[[Plain [Str "Second"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "5",Str ".",Str "0"]]
|
||||
,[Plain [Str "Here",Str "'",Str "s",Space,Str "another",Space,Str "one",Str ".",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows",Str "."]]]]
|
||||
|
@ -72,12 +71,12 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
|||
[[Plain [Str "Centered",Space,Str "Header"]]
|
||||
,[Plain [Str "Left",Space,Str "Aligned"]]
|
||||
,[Plain [Str "Right",Space,Str "Aligned"]]
|
||||
, [ Plain [Str "Default",Space,Str "aligned"] ] ] [
|
||||
[ [ Plain [Str "First"] ]
|
||||
,[Plain [Str "Default",Space,Str "aligned"]]]
|
||||
[[[Plain [Str "First"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "12",Str ".",Str "0"]]
|
||||
, [ Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines",Str "."] ] ],
|
||||
[ [ Plain [Str "Second"] ]
|
||||
,[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines",Str "."]]]
|
||||
,[[Plain [Str "Second"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "5",Str ".",Str "0"]]
|
||||
,[Plain [Str "Here",Str "'",Str "s",Space,Str "another",Space,Str "one",Str ".",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows",Str "."]]]]
|
||||
|
@ -86,16 +85,16 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
|||
[[]
|
||||
,[]
|
||||
,[]
|
||||
, [] ] [
|
||||
[ [ Plain [Str "12"] ]
|
||||
,[]]
|
||||
[[[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
, [ Plain [Str "12"] ] ],
|
||||
[ [ Plain [Str "123"] ]
|
||||
,[Plain [Str "12"]]]
|
||||
,[[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
, [ Plain [Str "123"] ] ],
|
||||
[ [ Plain [Str "1"] ]
|
||||
,[Plain [Str "123"]]]
|
||||
,[[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]]]
|
||||
|
@ -104,13 +103,12 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
|||
[[]
|
||||
,[]
|
||||
,[]
|
||||
, [] ] [
|
||||
[ [ Plain [Str "First"] ]
|
||||
,[]]
|
||||
[[[Plain [Str "First"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "12",Str ".",Str "0"]]
|
||||
, [ Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines",Str "."] ] ],
|
||||
[ [ Plain [Str "Second"] ]
|
||||
,[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines",Str "."]]]
|
||||
,[[Plain [Str "Second"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "5",Str ".",Str "0"]]
|
||||
,[Plain [Str "Here",Str "'",Str "s",Space,Str "another",Space,Str "one",Str ".",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows",Str "."]]]]]
|
||||
|
||||
|
|
|
@ -23,7 +23,6 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,Para [Str "E",Str "-",Str "mail",Space,Str "style",Str ":"]
|
||||
,BlockQuote
|
||||
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "block",Space,Str "quote",Str ".",Space,Str "It",Space,Str "is",Space,Str "pretty",Space,Str "short",Str "."]]
|
||||
|
||||
,BlockQuote
|
||||
[Para [Str "Code",Space,Str "in",Space,Str "a",Space,Str "block",Space,Str "quote",Str ":"]
|
||||
,CodeBlock ("",[],[]) "sub status {\n print \"working\";\n}"
|
||||
|
@ -34,10 +33,8 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,Para [Str "Nested",Space,Str "block",Space,Str "quotes",Str ":"]
|
||||
,BlockQuote
|
||||
[Para [Str "nested"]]
|
||||
|
||||
,BlockQuote
|
||||
[ Para [Str "nested"] ]
|
||||
]
|
||||
[Para [Str "nested"]]]
|
||||
,Para [Str "This",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "a",Space,Str "block",Space,Str "quote",Str ":",Space,Str "2",Space,Str ">",Space,Str "1",Str "."]
|
||||
,Para [Str "And",Space,Str "a",Space,Str "following",Space,Str "paragraph",Str "."]
|
||||
,HorizontalRule
|
||||
|
@ -103,7 +100,8 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,Para [Str "Multiple",Space,Str "paragraphs",Str ":"]
|
||||
,OrderedList (1,Decimal,Period)
|
||||
[[Para [Str "Item",Space,Str "1",Str ",",Space,Str "graf",Space,Str "one",Str "."]
|
||||
, Para [Str "Item",Space,Str "1",Str ".",Space,Str "graf",Space,Str "two",Str ".",Space,Str "The",Space,Str "quick",Space,Str "brown",Space,Str "fox",Space,Str "jumped",Space,Str "over",Space,Str "the",Space,Str "lazy",Space,Str "dog",Apostrophe,Str "s",Space,Str "back",Str "."] ], [ Para [Str "Item",Space,Str "2",Str "."] ]
|
||||
,Para [Str "Item",Space,Str "1",Str ".",Space,Str "graf",Space,Str "two",Str ".",Space,Str "The",Space,Str "quick",Space,Str "brown",Space,Str "fox",Space,Str "jumped",Space,Str "over",Space,Str "the",Space,Str "lazy",Space,Str "dog",Apostrophe,Str "s",Space,Str "back",Str "."]]
|
||||
,[Para [Str "Item",Space,Str "2",Str "."]]
|
||||
,[Para [Str "Item",Space,Str "3",Str "."]]]
|
||||
,Header 2 [Str "Nested"]
|
||||
,BulletList
|
||||
|
@ -111,8 +109,7 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,BulletList
|
||||
[[Plain [Str "Tab"]
|
||||
,BulletList
|
||||
[ [ Plain [Str "Tab"] ]
|
||||
] ] ] ] ]
|
||||
[[Plain [Str "Tab"]]]]]]]
|
||||
,Para [Str "Here",Apostrophe,Str "s",Space,Str "another",Str ":"]
|
||||
,OrderedList (1,Decimal,Period)
|
||||
[[Plain [Str "First"]]
|
||||
|
@ -120,7 +117,8 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,BulletList
|
||||
[[Plain [Str "Fee"]]
|
||||
,[Plain [Str "Fie"]]
|
||||
, [ Plain [Str "Foe"] ] ] ], [ Plain [Str "Third"] ] ]
|
||||
,[Plain [Str "Foe"]]]]
|
||||
,[Plain [Str "Third"]]]
|
||||
,Para [Str "Same",Space,Str "thing",Space,Str "but",Space,Str "with",Space,Str "paragraphs",Str ":"]
|
||||
,OrderedList (1,Decimal,Period)
|
||||
[[Para [Str "First"]]
|
||||
|
@ -128,7 +126,8 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,BulletList
|
||||
[[Plain [Str "Fee"]]
|
||||
,[Plain [Str "Fie"]]
|
||||
, [ Plain [Str "Foe"] ] ] ], [ Para [Str "Third"] ] ]
|
||||
,[Plain [Str "Foe"]]]]
|
||||
,[Para [Str "Third"]]]
|
||||
,Header 2 [Str "Tabs",Space,Str "and",Space,Str "spaces"]
|
||||
,BulletList
|
||||
[[Para [Str "this",Space,Str "is",Space,Str "a",Space,Str "list",Space,Str "item",Space,Str "indented",Space,Str "with",Space,Str "tabs"]]
|
||||
|
@ -155,15 +154,13 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,OrderedList (6,Decimal,TwoParens)
|
||||
[[Plain [Str "Decimal",Space,Str "start",Space,Str "with",Space,Str "6"]
|
||||
,OrderedList (3,LowerAlpha,OneParen)
|
||||
[ [ Plain [Str "Lower",Space,Str "alpha",Space,Str "with",Space,Str "paren"] ]
|
||||
] ] ] ] ] ] ]
|
||||
[[Plain [Str "Lower",Space,Str "alpha",Space,Str "with",Space,Str "paren"]]]]]]]]]
|
||||
,Para [Str "Autonumbering",Str ":"]
|
||||
,OrderedList (1,DefaultStyle,DefaultDelim)
|
||||
[[Plain [Str "Autonumber",Str "."]]
|
||||
,[Plain [Str "More",Str "."]
|
||||
,OrderedList (1,DefaultStyle,DefaultDelim)
|
||||
[ [ Plain [Str "Nested",Str "."] ]
|
||||
] ] ]
|
||||
[[Plain [Str "Nested",Str "."]]]]]
|
||||
,Para [Str "Should",Space,Str "not",Space,Str "be",Space,Str "a",Space,Str "list",Space,Str "item",Str ":"]
|
||||
,Para [Str "M.A.\160",Str "2007"]
|
||||
,Para [Str "B",Str ".",Space,Str "Williams"]
|
||||
|
@ -172,36 +169,27 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,Para [Str "Tight",Space,Str "using",Space,Str "spaces",Str ":"]
|
||||
,DefinitionList
|
||||
[([Str "apple"],
|
||||
[ [ Plain [Str "red",Space,Str "fruit"] ]
|
||||
])
|
||||
[[Plain [Str "red",Space,Str "fruit"]]])
|
||||
,([Str "orange"],
|
||||
[ [ Plain [Str "orange",Space,Str "fruit"] ]
|
||||
])
|
||||
[[Plain [Str "orange",Space,Str "fruit"]]])
|
||||
,([Str "banana"],
|
||||
[ [ Plain [Str "yellow",Space,Str "fruit"] ]
|
||||
]) ]
|
||||
[[Plain [Str "yellow",Space,Str "fruit"]]])]
|
||||
,Para [Str "Tight",Space,Str "using",Space,Str "tabs",Str ":"]
|
||||
,DefinitionList
|
||||
[([Str "apple"],
|
||||
[ [ Plain [Str "red",Space,Str "fruit"] ]
|
||||
])
|
||||
[[Plain [Str "red",Space,Str "fruit"]]])
|
||||
,([Str "orange"],
|
||||
[ [ Plain [Str "orange",Space,Str "fruit"] ]
|
||||
])
|
||||
[[Plain [Str "orange",Space,Str "fruit"]]])
|
||||
,([Str "banana"],
|
||||
[ [ Plain [Str "yellow",Space,Str "fruit"] ]
|
||||
]) ]
|
||||
[[Plain [Str "yellow",Space,Str "fruit"]]])]
|
||||
,Para [Str "Loose",Str ":"]
|
||||
,DefinitionList
|
||||
[([Str "apple"],
|
||||
[ [ Para [Str "red",Space,Str "fruit"] ]
|
||||
])
|
||||
[[Para [Str "red",Space,Str "fruit"]]])
|
||||
,([Str "orange"],
|
||||
[ [ Para [Str "orange",Space,Str "fruit"] ]
|
||||
])
|
||||
[[Para [Str "orange",Space,Str "fruit"]]])
|
||||
,([Str "banana"],
|
||||
[ [ Para [Str "yellow",Space,Str "fruit"] ]
|
||||
]) ]
|
||||
[[Para [Str "yellow",Space,Str "fruit"]]])]
|
||||
,Para [Str "Multiple",Space,Str "blocks",Space,Str "with",Space,Str "italics",Str ":"]
|
||||
,DefinitionList
|
||||
[([Emph [Str "apple"]],
|
||||
|
@ -211,34 +199,28 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
[[Para [Str "orange",Space,Str "fruit"]
|
||||
,CodeBlock ("",[],[]) "{ orange code block }"
|
||||
,BlockQuote
|
||||
[ Para [Str "orange",Space,Str "block",Space,Str "quote"] ]
|
||||
]]) ]
|
||||
[Para [Str "orange",Space,Str "block",Space,Str "quote"]]]])]
|
||||
,Para [Str "Multiple",Space,Str "definitions",Str ",",Space,Str "tight",Str ":"]
|
||||
,DefinitionList
|
||||
[([Str "apple"],
|
||||
[[Plain [Str "red",Space,Str "fruit"]]
|
||||
, [ Plain [Str "computer"] ]
|
||||
])
|
||||
,[Plain [Str "computer"]]])
|
||||
,([Str "orange"],
|
||||
[[Plain [Str "orange",Space,Str "fruit"]]
|
||||
, [ Plain [Str "bank"] ]
|
||||
]) ]
|
||||
,[Plain [Str "bank"]]])]
|
||||
,Para [Str "Multiple",Space,Str "definitions",Str ",",Space,Str "loose",Str ":"]
|
||||
,DefinitionList
|
||||
[([Str "apple"],
|
||||
[[Para [Str "red",Space,Str "fruit"]]
|
||||
, [ Para [Str "computer"] ]
|
||||
])
|
||||
,[Para [Str "computer"]]])
|
||||
,([Str "orange"],
|
||||
[[Para [Str "orange",Space,Str "fruit"]]
|
||||
, [ Para [Str "bank"] ]
|
||||
]) ]
|
||||
,[Para [Str "bank"]]])]
|
||||
,Para [Str "Blank",Space,Str "line",Space,Str "after",Space,Str "term",Str ",",Space,Str "indented",Space,Str "marker",Str ",",Space,Str "alternate",Space,Str "markers",Str ":"]
|
||||
,DefinitionList
|
||||
[([Str "apple"],
|
||||
[[Para [Str "red",Space,Str "fruit"]]
|
||||
, [ Para [Str "computer"] ]
|
||||
])
|
||||
,[Para [Str "computer"]]])
|
||||
,([Str "orange"],
|
||||
[[Para [Str "orange",Space,Str "fruit"]
|
||||
,OrderedList (1,Decimal,Period)
|
||||
|
@ -397,7 +379,6 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,Para [Str "An",Space,Str "e",Str "-",Str "mail",Space,Str "address",Str ":",Space,Link [Code "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")]
|
||||
,BlockQuote
|
||||
[Para [Str "Blockquoted",Str ":",Space,Link [Code "http://example.com/"] ("http://example.com/","")]]
|
||||
|
||||
,Para [Str "Auto",Str "-",Str "links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here",Str ":",Space,Code "<http://example.com/>"]
|
||||
,CodeBlock ("",[],[]) "or here: <http://example.com/>"
|
||||
,HorizontalRule
|
||||
|
@ -410,8 +391,6 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference",Str ",",Note [Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote",Str ".",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "after",Space,Str "the",Space,Str "footnote",Space,Str "reference",Str ".",Space,Str "It",Space,Str "need",Space,Str "not",Space,Str "be",Space,Str "placed",Space,Str "at",Space,Str "the",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "document",Str "."]],Space,Str "and",Space,Str "another",Str ".",Note [Para [Str "Here",Apostrophe,Str "s",Space,Str "the",Space,Str "long",Space,Str "note",Str ".",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks",Str "."],Para [Str "Subsequent",Space,Str "blocks",Space,Str "are",Space,Str "indented",Space,Str "to",Space,Str "show",Space,Str "that",Space,Str "they",Space,Str "belong",Space,Str "to",Space,Str "the",Space,Str "footnote",Space,Str "(",Str "as",Space,Str "with",Space,Str "list",Space,Str "items",Str ")",Str "."],CodeBlock ("",[],[]) " { <code> }",Para [Str "If",Space,Str "you",Space,Str "want",Str ",",Space,Str "you",Space,Str "can",Space,Str "indent",Space,Str "every",Space,Str "line",Str ",",Space,Str "but",Space,Str "you",Space,Str "can",Space,Str "also",Space,Str "be",Space,Str "lazy",Space,Str "and",Space,Str "just",Space,Str "indent",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "each",Space,Str "block",Str "."]],Space,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference",Str ",",Space,Str "because",Space,Str "it",Space,Str "contains",Space,Str "a",Space,Str "space",Str ".",Str "[",Str "^",Str "my",Space,Str "note",Str "]",Space,Str "Here",Space,Str "is",Space,Str "an",Space,Str "inline",Space,Str "note",Str ".",Note [Para [Str "This",Space,Str "is",Space,Emph [Str "easier"],Space,Str "to",Space,Str "type",Str ".",Space,Str "Inline",Space,Str "notes",Space,Str "may",Space,Str "contain",Space,Link [Str "links"] ("http://google.com",""),Space,Str "and",Space,Code "]",Space,Str "verbatim",Space,Str "characters",Str ",",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "[",Str "bracketed",Space,Str "text",Str "]",Str "."]]]
|
||||
,BlockQuote
|
||||
[Para [Str "Notes",Space,Str "can",Space,Str "go",Space,Str "in",Space,Str "quotes",Str ".",Note [Para [Str "In",Space,Str "quote",Str "."]]]]
|
||||
|
||||
,OrderedList (1,Decimal,Period)
|
||||
[ [ Plain [Str "And",Space,Str "in",Space,Str "list",Space,Str "items",Str ".",Note [Para [Str "In",Space,Str "list",Str "."]]] ]
|
||||
]
|
||||
[[Plain [Str "And",Space,Str "in",Space,Str "list",Space,Str "items",Str ".",Note [Para [Str "In",Space,Str "list",Str "."]]]]]
|
||||
,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",Str ",",Space,Str "as",Space,Str "it",Space,Str "is",Space,Str "not",Space,Str "indented",Str "."]]
|
|
@ -12,14 +12,12 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
|||
,Para [Str "Line",Space,Str "breaks",Space,Str "are",Space,Str "preserved",Space,Str "in",Space,Str "textile",Str ",",Space,Str "so",Space,Str "you",Space,Str "can",Space,Str "not",Space,Str "wrap",Space,Str "your",Space,Str "very",LineBreak,Str "long",Space,Str "paragraph",Space,Str "with",Space,Str "your",Space,Str "favourite",Space,Str "text",Space,Str "editor",Space,Str "and",Space,Str "have",Space,Str "it",Space,Str "rendered",LineBreak,Str "with",Space,Str "no",Space,Str "break",Str "."]
|
||||
,Para [Str "Here",Apostrophe,Str "s",Space,Str "one",Space,Str "with",Space,Str "a",Space,Str "bullet",Str "."]
|
||||
,BulletList
|
||||
[ [ Plain [Str "criminey",Str "."] ]
|
||||
]
|
||||
[[Plain [Str "criminey",Str "."]]]
|
||||
,Para [Str "There",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "paragraph",Space,Str "break",Space,Str "between",Space,Str "here"]
|
||||
,Para [Str "and",Space,Str "here",Str "."]
|
||||
,Header 1 [Str "Block",Space,Str "Quotes"]
|
||||
,BlockQuote
|
||||
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "famous",Space,Str "quote",Space,Str "from",Space,Str "somebody",Str ".",Space,Str "He",Space,Str "had",Space,Str "a",Space,Str "lot",Space,Str "of",Space,Str "things",Space,Str "to",LineBreak,Str "say",Str ",",Space,Str "so",Space,Str "the",Space,Str "text",Space,Str "is",Space,Str "really",Space,Str "really",Space,Str "long",Space,Str "and",Space,Str "spans",Space,Str "on",Space,Str "multiple",Space,Str "lines",Str "."]]
|
||||
|
||||
,Para [Str "And",Space,Str "a",Space,Str "following",Space,Str "paragraph",Str "."]
|
||||
,Header 1 [Str "Code",Space,Str "Blocks"]
|
||||
,Para [Str "Code",Str ":"]
|
||||
|
@ -46,7 +44,9 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
|||
[[Plain [Str "ui",Space,Str "1",Str ".",Str "1"]
|
||||
,OrderedList (1,DefaultStyle,DefaultDelim)
|
||||
[[Plain [Str "oi",Space,Str "1",Str ".",Str "1",Str ".",Str "1"]]
|
||||
, [ Plain [Str "oi",Space,Str "1",Str ".",Str "1",Str ".",Str "2"] ] ] ], [ Plain [Str "ui",Space,Str "1",Str ".",Str "2"] ] ] ], [ Plain [Str "ui",Space,Str "2"]
|
||||
,[Plain [Str "oi",Space,Str "1",Str ".",Str "1",Str ".",Str "2"]]]]
|
||||
,[Plain [Str "ui",Space,Str "1",Str ".",Str "2"]]]]
|
||||
,[Plain [Str "ui",Space,Str "2"]
|
||||
,OrderedList (1,DefaultStyle,DefaultDelim)
|
||||
[[Plain [Str "oi",Space,Str "2",Str ".",Str "1"]
|
||||
,BulletList
|
||||
|
@ -55,17 +55,14 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
|||
,Header 2 [Str "Definition",Space,Str "List"]
|
||||
,DefinitionList
|
||||
[([Str "coffee"],
|
||||
[ [ Plain [Str "Hot",Space,Str "and",Space,Str "black"] ]
|
||||
])
|
||||
[[Plain [Str "Hot",Space,Str "and",Space,Str "black"]]])
|
||||
,([Str "tea"],
|
||||
[ [ Plain [Str "Also",Space,Str "hot",Str ",",Space,Str "but",Space,Str "a",Space,Str "little",Space,Str "less",Space,Str "black"] ]
|
||||
])
|
||||
[[Plain [Str "Also",Space,Str "hot",Str ",",Space,Str "but",Space,Str "a",Space,Str "little",Space,Str "less",Space,Str "black"]]])
|
||||
,([Str "milk"],
|
||||
[[Para [Str "Nourishing",Space,Str "beverage",Space,Str "for",Space,Str "baby",Space,Str "cows",Str "."]
|
||||
,Para [Str "Cold",Space,Str "drink",Space,Str "that",Space,Str "goes",Space,Str "great",Space,Str "with",Space,Str "cookies",Str "."]]])
|
||||
,([Str "beer"],
|
||||
[ [ Plain [Str "fresh",Space,Str "and",Space,Str "bitter"] ]
|
||||
]) ]
|
||||
[[Plain [Str "fresh",Space,Str "and",Space,Str "bitter"]]])]
|
||||
,Header 1 [Str "Inline",Space,Str "Markup"]
|
||||
,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str ".",LineBreak,Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str ".",LineBreak,Str "A",Space,Link [Strong [Str "strong",Space,Str "link"]] ("http://www.foobar.com",""),Str "."]
|
||||
,Para [Emph [Strong [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em",Str "."]],LineBreak,Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word",Space,Str "and",Space,Emph [Strong [Str "that",Space,Str "one"]],Str ".",LineBreak,Strikeout [Str "This",Space,Str "is",Space,Str "strikeout",Space,Str "and",Space,Strong [Str "strong"]]]
|
||||
|
@ -82,18 +79,17 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
|||
,Para [Str "Textile",Space,Str "allows",Space,Str "tables",Space,Str "with",Space,Str "and",Space,Str "without",Space,Str "headers",Space,Str ":"]
|
||||
,Header 2 [Str "Without",Space,Str "headers"]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[
|
||||
] [
|
||||
[ [ Plain [Str "name"] ]
|
||||
[]
|
||||
[[[Plain [Str "name"]]
|
||||
,[Plain [Str "age"]]
|
||||
, [ Plain [Str "sex"] ] ],
|
||||
[ [ Plain [Str "joan"] ]
|
||||
,[Plain [Str "sex"]]]
|
||||
,[[Plain [Str "joan"]]
|
||||
,[Plain [Str "24"]]
|
||||
, [ Plain [Str "f"] ] ],
|
||||
[ [ Plain [Str "archie"] ]
|
||||
,[Plain [Str "f"]]]
|
||||
,[[Plain [Str "archie"]]
|
||||
,[Plain [Str "29"]]
|
||||
, [ Plain [Str "m"] ] ],
|
||||
[ [ Plain [Str "bella"] ]
|
||||
,[Plain [Str "m"]]]
|
||||
,[[Plain [Str "bella"]]
|
||||
,[Plain [Str "45"]]
|
||||
,[Plain [Str "f"]]]]
|
||||
,Para [Str "and",Space,Str "some",Space,Str "text",Space,Str "following",Space,Ellipses]
|
||||
|
@ -101,14 +97,14 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
|||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[[Plain [Str "name"]]
|
||||
,[Plain [Str "age"]]
|
||||
, [ Plain [Str "sex"] ] ] [
|
||||
[ [ Plain [Str "joan"] ]
|
||||
,[Plain [Str "sex"]]]
|
||||
[[[Plain [Str "joan"]]
|
||||
,[Plain [Str "24"]]
|
||||
, [ Plain [Str "f"] ] ],
|
||||
[ [ Plain [Str "archie"] ]
|
||||
,[Plain [Str "f"]]]
|
||||
,[[Plain [Str "archie"]]
|
||||
,[Plain [Str "29"]]
|
||||
, [ Plain [Str "m"] ] ],
|
||||
[ [ Plain [Str "bella"] ]
|
||||
,[Plain [Str "m"]]]
|
||||
,[[Plain [Str "bella"]]
|
||||
,[Plain [Str "45"]]
|
||||
,[Plain [Str "f"]]]]
|
||||
,Header 1 [Str "Images"]
|
||||
|
@ -118,12 +114,11 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
|
|||
,Para [Str "as",Space,Str "well",Space,Str "as",Space,Strong [Str "inline",Space,Str "attributes"],Space,Str "of",Space,Str " all kind"]
|
||||
,Para [Str "and",Space,Str "paragraph",Space,Str "attributes",Str ",",Space,Str "and",Space,Str "table",Space,Str "attributes",Str "."]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[
|
||||
] [
|
||||
[ [ Plain [Str "name"] ]
|
||||
[]
|
||||
[[[Plain [Str "name"]]
|
||||
,[Plain [Str "age"]]
|
||||
, [ Plain [Str "sex"] ] ],
|
||||
[ [ Plain [Str "joan"] ]
|
||||
,[Plain [Str "sex"]]]
|
||||
,[[Plain [Str "joan"]]
|
||||
,[Plain [Str "24"]]
|
||||
,[Plain [Str "f"]]]]
|
||||
,Header 1 [Str "Raw",Space,Str "HTML"]
|
||||
|
|
|
@ -23,7 +23,6 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,Para [Str "E",Str "-",Str "mail",Space,Str "style",Str ":"]
|
||||
,BlockQuote
|
||||
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "block",Space,Str "quote",Str ".",Space,Str "It",Space,Str "is",Space,Str "pretty",Space,Str "short",Str "."]]
|
||||
|
||||
,BlockQuote
|
||||
[Para [Str "Code",Space,Str "in",Space,Str "a",Space,Str "block",Space,Str "quote",Str ":"]
|
||||
,CodeBlock ("",[],[]) "sub status {\n print \"working\";\n}"
|
||||
|
@ -34,10 +33,8 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,Para [Str "Nested",Space,Str "block",Space,Str "quotes",Str ":"]
|
||||
,BlockQuote
|
||||
[Para [Str "nested"]]
|
||||
|
||||
,BlockQuote
|
||||
[ Para [Str "nested"] ]
|
||||
]
|
||||
[Para [Str "nested"]]]
|
||||
,Para [Str "This",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "a",Space,Str "block",Space,Str "quote",Str ":",Space,Str "2",Space,Str ">",Space,Str "1",Str "."]
|
||||
,Para [Str "And",Space,Str "a",Space,Str "following",Space,Str "paragraph",Str "."]
|
||||
,HorizontalRule
|
||||
|
@ -103,7 +100,8 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,Para [Str "Multiple",Space,Str "paragraphs",Str ":"]
|
||||
,OrderedList (1,Decimal,Period)
|
||||
[[Para [Str "Item",Space,Str "1",Str ",",Space,Str "graf",Space,Str "one",Str "."]
|
||||
, Para [Str "Item",Space,Str "1",Str ".",Space,Str "graf",Space,Str "two",Str ".",Space,Str "The",Space,Str "quick",Space,Str "brown",Space,Str "fox",Space,Str "jumped",Space,Str "over",Space,Str "the",Space,Str "lazy",Space,Str "dog",Apostrophe,Str "s",Space,Str "back",Str "."] ], [ Para [Str "Item",Space,Str "2",Str "."] ]
|
||||
,Para [Str "Item",Space,Str "1",Str ".",Space,Str "graf",Space,Str "two",Str ".",Space,Str "The",Space,Str "quick",Space,Str "brown",Space,Str "fox",Space,Str "jumped",Space,Str "over",Space,Str "the",Space,Str "lazy",Space,Str "dog",Apostrophe,Str "s",Space,Str "back",Str "."]]
|
||||
,[Para [Str "Item",Space,Str "2",Str "."]]
|
||||
,[Para [Str "Item",Space,Str "3",Str "."]]]
|
||||
,Header 2 [Str "Nested"]
|
||||
,BulletList
|
||||
|
@ -111,8 +109,7 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,BulletList
|
||||
[[Plain [Str "Tab"]
|
||||
,BulletList
|
||||
[ [ Plain [Str "Tab"] ]
|
||||
] ] ] ] ]
|
||||
[[Plain [Str "Tab"]]]]]]]
|
||||
,Para [Str "Here",Apostrophe,Str "s",Space,Str "another",Str ":"]
|
||||
,OrderedList (1,Decimal,Period)
|
||||
[[Plain [Str "First"]]
|
||||
|
@ -120,7 +117,8 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,BulletList
|
||||
[[Plain [Str "Fee"]]
|
||||
,[Plain [Str "Fie"]]
|
||||
, [ Plain [Str "Foe"] ] ] ], [ Plain [Str "Third"] ] ]
|
||||
,[Plain [Str "Foe"]]]]
|
||||
,[Plain [Str "Third"]]]
|
||||
,Para [Str "Same",Space,Str "thing",Space,Str "but",Space,Str "with",Space,Str "paragraphs",Str ":"]
|
||||
,OrderedList (1,Decimal,Period)
|
||||
[[Para [Str "First"]]
|
||||
|
@ -128,7 +126,8 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,BulletList
|
||||
[[Plain [Str "Fee"]]
|
||||
,[Plain [Str "Fie"]]
|
||||
, [ Plain [Str "Foe"] ] ] ], [ Para [Str "Third"] ] ]
|
||||
,[Plain [Str "Foe"]]]]
|
||||
,[Para [Str "Third"]]]
|
||||
,Header 2 [Str "Tabs",Space,Str "and",Space,Str "spaces"]
|
||||
,BulletList
|
||||
[[Para [Str "this",Space,Str "is",Space,Str "a",Space,Str "list",Space,Str "item",Space,Str "indented",Space,Str "with",Space,Str "tabs"]]
|
||||
|
@ -155,15 +154,13 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,OrderedList (6,Decimal,TwoParens)
|
||||
[[Plain [Str "Decimal",Space,Str "start",Space,Str "with",Space,Str "6"]
|
||||
,OrderedList (3,LowerAlpha,OneParen)
|
||||
[ [ Plain [Str "Lower",Space,Str "alpha",Space,Str "with",Space,Str "paren"] ]
|
||||
] ] ] ] ] ] ]
|
||||
[[Plain [Str "Lower",Space,Str "alpha",Space,Str "with",Space,Str "paren"]]]]]]]]]
|
||||
,Para [Str "Autonumbering",Str ":"]
|
||||
,OrderedList (1,DefaultStyle,DefaultDelim)
|
||||
[[Plain [Str "Autonumber",Str "."]]
|
||||
,[Plain [Str "More",Str "."]
|
||||
,OrderedList (1,DefaultStyle,DefaultDelim)
|
||||
[ [ Plain [Str "Nested",Str "."] ]
|
||||
] ] ]
|
||||
[[Plain [Str "Nested",Str "."]]]]]
|
||||
,Para [Str "Should",Space,Str "not",Space,Str "be",Space,Str "a",Space,Str "list",Space,Str "item",Str ":"]
|
||||
,Para [Str "M.A.\160",Str "2007"]
|
||||
,Para [Str "B",Str ".",Space,Str "Williams"]
|
||||
|
@ -172,36 +169,27 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,Para [Str "Tight",Space,Str "using",Space,Str "spaces",Str ":"]
|
||||
,DefinitionList
|
||||
[([Str "apple"],
|
||||
[ [ Plain [Str "red",Space,Str "fruit"] ]
|
||||
])
|
||||
[[Plain [Str "red",Space,Str "fruit"]]])
|
||||
,([Str "orange"],
|
||||
[ [ Plain [Str "orange",Space,Str "fruit"] ]
|
||||
])
|
||||
[[Plain [Str "orange",Space,Str "fruit"]]])
|
||||
,([Str "banana"],
|
||||
[ [ Plain [Str "yellow",Space,Str "fruit"] ]
|
||||
]) ]
|
||||
[[Plain [Str "yellow",Space,Str "fruit"]]])]
|
||||
,Para [Str "Tight",Space,Str "using",Space,Str "tabs",Str ":"]
|
||||
,DefinitionList
|
||||
[([Str "apple"],
|
||||
[ [ Plain [Str "red",Space,Str "fruit"] ]
|
||||
])
|
||||
[[Plain [Str "red",Space,Str "fruit"]]])
|
||||
,([Str "orange"],
|
||||
[ [ Plain [Str "orange",Space,Str "fruit"] ]
|
||||
])
|
||||
[[Plain [Str "orange",Space,Str "fruit"]]])
|
||||
,([Str "banana"],
|
||||
[ [ Plain [Str "yellow",Space,Str "fruit"] ]
|
||||
]) ]
|
||||
[[Plain [Str "yellow",Space,Str "fruit"]]])]
|
||||
,Para [Str "Loose",Str ":"]
|
||||
,DefinitionList
|
||||
[([Str "apple"],
|
||||
[ [ Para [Str "red",Space,Str "fruit"] ]
|
||||
])
|
||||
[[Para [Str "red",Space,Str "fruit"]]])
|
||||
,([Str "orange"],
|
||||
[ [ Para [Str "orange",Space,Str "fruit"] ]
|
||||
])
|
||||
[[Para [Str "orange",Space,Str "fruit"]]])
|
||||
,([Str "banana"],
|
||||
[ [ Para [Str "yellow",Space,Str "fruit"] ]
|
||||
]) ]
|
||||
[[Para [Str "yellow",Space,Str "fruit"]]])]
|
||||
,Para [Str "Multiple",Space,Str "blocks",Space,Str "with",Space,Str "italics",Str ":"]
|
||||
,DefinitionList
|
||||
[([Emph [Str "apple"]],
|
||||
|
@ -211,34 +199,28 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
[[Para [Str "orange",Space,Str "fruit"]
|
||||
,CodeBlock ("",[],[]) "{ orange code block }"
|
||||
,BlockQuote
|
||||
[ Para [Str "orange",Space,Str "block",Space,Str "quote"] ]
|
||||
]]) ]
|
||||
[Para [Str "orange",Space,Str "block",Space,Str "quote"]]]])]
|
||||
,Para [Str "Multiple",Space,Str "definitions",Str ",",Space,Str "tight",Str ":"]
|
||||
,DefinitionList
|
||||
[([Str "apple"],
|
||||
[[Plain [Str "red",Space,Str "fruit"]]
|
||||
, [ Plain [Str "computer"] ]
|
||||
])
|
||||
,[Plain [Str "computer"]]])
|
||||
,([Str "orange"],
|
||||
[[Plain [Str "orange",Space,Str "fruit"]]
|
||||
, [ Plain [Str "bank"] ]
|
||||
]) ]
|
||||
,[Plain [Str "bank"]]])]
|
||||
,Para [Str "Multiple",Space,Str "definitions",Str ",",Space,Str "loose",Str ":"]
|
||||
,DefinitionList
|
||||
[([Str "apple"],
|
||||
[[Para [Str "red",Space,Str "fruit"]]
|
||||
, [ Para [Str "computer"] ]
|
||||
])
|
||||
,[Para [Str "computer"]]])
|
||||
,([Str "orange"],
|
||||
[[Para [Str "orange",Space,Str "fruit"]]
|
||||
, [ Para [Str "bank"] ]
|
||||
]) ]
|
||||
,[Para [Str "bank"]]])]
|
||||
,Para [Str "Blank",Space,Str "line",Space,Str "after",Space,Str "term",Str ",",Space,Str "indented",Space,Str "marker",Str ",",Space,Str "alternate",Space,Str "markers",Str ":"]
|
||||
,DefinitionList
|
||||
[([Str "apple"],
|
||||
[[Para [Str "red",Space,Str "fruit"]]
|
||||
, [ Para [Str "computer"] ]
|
||||
])
|
||||
,[Para [Str "computer"]]])
|
||||
,([Str "orange"],
|
||||
[[Para [Str "orange",Space,Str "fruit"]
|
||||
,OrderedList (1,Decimal,Period)
|
||||
|
@ -397,7 +379,6 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,Para [Str "An",Space,Str "e",Str "-",Str "mail",Space,Str "address",Str ":",Space,Link [Code "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")]
|
||||
,BlockQuote
|
||||
[Para [Str "Blockquoted",Str ":",Space,Link [Code "http://example.com/"] ("http://example.com/","")]]
|
||||
|
||||
,Para [Str "Auto",Str "-",Str "links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here",Str ":",Space,Code "<http://example.com/>"]
|
||||
,CodeBlock ("",[],[]) "or here: <http://example.com/>"
|
||||
,HorizontalRule
|
||||
|
@ -410,8 +391,6 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference",Str ",",Note [Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote",Str ".",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "after",Space,Str "the",Space,Str "footnote",Space,Str "reference",Str ".",Space,Str "It",Space,Str "need",Space,Str "not",Space,Str "be",Space,Str "placed",Space,Str "at",Space,Str "the",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "document",Str "."]],Space,Str "and",Space,Str "another",Str ".",Note [Para [Str "Here",Apostrophe,Str "s",Space,Str "the",Space,Str "long",Space,Str "note",Str ".",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks",Str "."],Para [Str "Subsequent",Space,Str "blocks",Space,Str "are",Space,Str "indented",Space,Str "to",Space,Str "show",Space,Str "that",Space,Str "they",Space,Str "belong",Space,Str "to",Space,Str "the",Space,Str "footnote",Space,Str "(",Str "as",Space,Str "with",Space,Str "list",Space,Str "items",Str ")",Str "."],CodeBlock ("",[],[]) " { <code> }",Para [Str "If",Space,Str "you",Space,Str "want",Str ",",Space,Str "you",Space,Str "can",Space,Str "indent",Space,Str "every",Space,Str "line",Str ",",Space,Str "but",Space,Str "you",Space,Str "can",Space,Str "also",Space,Str "be",Space,Str "lazy",Space,Str "and",Space,Str "just",Space,Str "indent",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "each",Space,Str "block",Str "."]],Space,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference",Str ",",Space,Str "because",Space,Str "it",Space,Str "contains",Space,Str "a",Space,Str "space",Str ".",Str "[",Str "^",Str "my",Space,Str "note",Str "]",Space,Str "Here",Space,Str "is",Space,Str "an",Space,Str "inline",Space,Str "note",Str ".",Note [Para [Str "This",Space,Str "is",Space,Emph [Str "easier"],Space,Str "to",Space,Str "type",Str ".",Space,Str "Inline",Space,Str "notes",Space,Str "may",Space,Str "contain",Space,Link [Str "links"] ("http://google.com",""),Space,Str "and",Space,Code "]",Space,Str "verbatim",Space,Str "characters",Str ",",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "[",Str "bracketed",Space,Str "text",Str "]",Str "."]]]
|
||||
,BlockQuote
|
||||
[Para [Str "Notes",Space,Str "can",Space,Str "go",Space,Str "in",Space,Str "quotes",Str ".",Note [Para [Str "In",Space,Str "quote",Str "."]]]]
|
||||
|
||||
,OrderedList (1,Decimal,Period)
|
||||
[ [ Plain [Str "And",Space,Str "in",Space,Str "list",Space,Str "items",Str ".",Note [Para [Str "In",Space,Str "list",Str "."]]] ]
|
||||
]
|
||||
[[Plain [Str "And",Space,Str "in",Space,Str "list",Space,Str "items",Str ".",Note [Para [Str "In",Space,Str "list",Str "."]]]]]
|
||||
,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",Str ",",Space,Str "as",Space,Str "it",Space,Str "is",Space,Str "not",Space,Str "indented",Str "."]]
|
Loading…
Add table
Reference in a new issue