diff options
author | despresc <christian.j.j.despres@gmail.com> | 2020-03-28 18:22:48 -0400 |
---|---|---|
committer | despresc <christian.j.j.despres@gmail.com> | 2020-04-15 23:03:22 -0400 |
commit | 7254a2ae0ba40b29c04b8924f27739614229432b (patch) | |
tree | 114e3143953451e3212511e7bf2e178548d3e1bd /test | |
parent | 83c1ce1d77d3ef058e4e5c645a8eb0379fab780f (diff) | |
download | pandoc-7254a2ae0ba40b29c04b8924f27739614229432b.tar.gz |
Implement the new Table type
Diffstat (limited to 'test')
57 files changed, 4361 insertions, 1863 deletions
diff --git a/test/Tests/Readers/DokuWiki.hs b/test/Tests/Readers/DokuWiki.hs index a5cce035c..52b4764a5 100644 --- a/test/Tests/Readers/DokuWiki.hs +++ b/test/Tests/Readers/DokuWiki.hs @@ -296,7 +296,7 @@ tests = [ testGroup "inlines" T.unlines [ "| foo | bar |" , "| bat | baz |" ] =?> - table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] + table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)] [] [[plain "foo", plain "bar"] ,[plain "bat", plain "baz"]] @@ -304,7 +304,7 @@ tests = [ testGroup "inlines" T.unlines [ "^ foo ^ bar ^" , "| bat | baz |" ] =?> - table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] + table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)] [plain "foo", plain "bar"] [[plain "bat", plain "baz"]] , "Table with colspan" =: @@ -312,7 +312,7 @@ tests = [ testGroup "inlines" , "| 1,0 | 1,1 ||" , "| 2,0 | 2,1 | 2,2 |" ] =?> - table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0), (AlignDefault, 0.0)] + table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing), (AlignDefault, Nothing)] [plain "0,0", plain "0,1", plain "0,2"] [[plain "1,0", plain "1,1", mempty] ,[plain "2,0", plain "2,1", plain "2,2"] diff --git a/test/Tests/Readers/LaTeX.hs b/test/Tests/Readers/LaTeX.hs index af412cfb3..098848769 100644 --- a/test/Tests/Readers/LaTeX.hs +++ b/test/Tests/Readers/LaTeX.hs @@ -36,7 +36,7 @@ infix 4 =: (=:) = test latex simpleTable' :: [Alignment] -> [[Blocks]] -> Blocks -simpleTable' aligns = table "" (zip aligns (repeat 0.0)) +simpleTable' aligns = table "" (zip aligns (repeat Nothing)) (map (const mempty) aligns) tokUntokRt :: String -> Bool diff --git a/test/Tests/Readers/Man.hs b/test/Tests/Readers/Man.hs index fe3e80a35..f358630bb 100644 --- a/test/Tests/Readers/Man.hs +++ b/test/Tests/Readers/Man.hs @@ -122,12 +122,12 @@ tests = [ testGroup "Tables" [ "t1" =: ".TS\nallbox;\nl l l.\na\tb\tc\nd\te\tf\n.TE" - =?> table mempty (replicate 3 (AlignLeft, 0.0)) [] [ + =?> table mempty (replicate 3 (AlignLeft, Nothing)) [] [ map (plain . str ) ["a", "b", "c"], map (plain . str ) ["d", "e", "f"] ], "longcell" =: ".TS\n;\nr.\nT{\na\nb\nc d\nT}\nf\n.TE" - =?> table mempty [(AlignRight, 0.0)] [] [[plain $ text "a b c d"], [plain $ str "f"]] + =?> table mempty [(AlignRight, Nothing)] [] [[plain $ text "a b c d"], [plain $ str "f"]] ] ] diff --git a/test/Tests/Readers/Muse.hs b/test/Tests/Readers/Muse.hs index 8edeebbf5..abf9e1ced 100644 --- a/test/Tests/Readers/Muse.hs +++ b/test/Tests/Readers/Muse.hs @@ -15,6 +15,7 @@ module Tests.Readers.Muse (tests) where import Prelude import Data.List (intersperse) +import Data.Maybe (isNothing) import Data.Monoid (Any (..)) import Data.Text (Text) import qualified Data.Text as T @@ -25,7 +26,7 @@ import Tests.Helpers import Text.Pandoc import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder -import Text.Pandoc.Shared (underlineSpan) +import Text.Pandoc.Shared (underlineSpan, toLegacyTable) import Text.Pandoc.Walk amuse :: Text -> Pandoc @@ -45,20 +46,41 @@ spcSep = mconcat . intersperse space -- Tables don't round-trip yet -- makeRoundTrip :: Block -> Block -makeRoundTrip t@(Table _caption aligns widths headers rows) = +makeRoundTrip t@(Table tattr blkCapt specs rhs thead tbody tfoot) = if isSimple && numcols > 1 then t else Para [Str "table was here"] - where numcols = maximum (length aligns : length widths : map length (headers:rows)) - hasSimpleCells = all isSimpleCell (concat (headers:rows)) + where (_, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot + numcols = maximum (length aligns : length widths : map length (headers:rows)) + hasSimpleCells = all isSimpleRow (thead <> tbody <> tfoot) isLineBreak LineBreak = Any True isLineBreak _ = Any False hasLineBreak = getAny . query isLineBreak - isSimple = hasSimpleCells && all (== 0) widths - isSimpleCell [Plain ils] = not (hasLineBreak ils) - isSimpleCell [Para ils ] = not (hasLineBreak ils) - isSimpleCell [] = True - isSimpleCell _ = False + isSimple = and [ hasSimpleCells + , all (== 0) widths + , null tfoot + , length thead == 1 + , isNullAttr tattr + , rhs == 0 + , simpleCapt ] + isNullAttr ("", [], []) = True + isNullAttr _ = False + isSimpleRow (Row attr body) = isNullAttr attr && all isSimpleCell body + isSimpleCell (Cell attr ali h w body) + = and [ h == 1 + , w == 1 + , isNullAttr attr + , isNothing ali + , isSimpleCellBody body ] + isSimpleCellBody [Plain ils] = not (hasLineBreak ils) + isSimpleCellBody [Para ils ] = not (hasLineBreak ils) + isSimpleCellBody [] = True + isSimpleCellBody _ = False + simpleCapt = case blkCapt of + Caption Nothing [Para _] -> True + Caption Nothing [Plain _] -> True + _ -> False + makeRoundTrip (OrderedList (start, LowerAlpha, _) items) = OrderedList (start, Decimal, Period) items makeRoundTrip (OrderedList (start, UpperAlpha, _) items) = OrderedList (start, Decimal, Period) items makeRoundTrip x = x @@ -950,12 +972,12 @@ tests = , testGroup "Tables" [ "Two cell table" =: "One | Two" =?> - table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] + table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)] [] [[plain "One", plain "Two"]] , "Table with multiple words" =: "One two | three four" =?> - table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] + table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)] [] [[plain "One two", plain "three four"]] , "Not a table" =: @@ -969,7 +991,7 @@ tests = [ "One | Two" , "Three | Four" ] =?> - table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] + table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)] [] [[plain "One", plain "Two"], [plain "Three", plain "Four"]] @@ -978,7 +1000,7 @@ tests = [ "First || Second" , "Third | Fourth" ] =?> - table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] + table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)] [plain "First", plain "Second"] [[plain "Third", plain "Fourth"]] , "Table with two headers" =: @@ -987,7 +1009,7 @@ tests = , "Second || header" , "Foo | bar" ] =?> - table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] + table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)] [plain "First", plain "header"] [[plain "Second", plain "header"], [plain "Foo", plain "bar"]] @@ -997,7 +1019,7 @@ tests = , "Baz || foo" , "Bar | baz" ] =?> - table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] + table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)] [plain "Baz", plain "foo"] [[plain "Bar", plain "baz"], [plain "Foo", plain "bar"]] @@ -1008,7 +1030,7 @@ tests = , "Second | row | there" , "|+ Table caption +|" ] =?> - table (text "Table caption") (replicate 3 (AlignDefault, 0.0)) + table (text "Table caption") (replicate 3 (AlignDefault, Nothing)) [plain "Foo", plain "bar", plain "baz"] [[plain "First", plain "row", plain "here"], [plain "Second", plain "row", plain "there"]] @@ -1017,7 +1039,7 @@ tests = [ "Foo | bar" , "|+ Table + caption +|" ] =?> - table (text "Table + caption") (replicate 2 (AlignDefault, 0.0)) + table (text "Table + caption") (replicate 2 (AlignDefault, Nothing)) [] [[plain "Foo", plain "bar"]] , "Caption without table" =: @@ -1029,7 +1051,7 @@ tests = , " Baz | foo" , " Bar | baz" ] =?> - table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] + table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)] [] [[plain "Foo", plain "bar"], [plain "Baz", plain "foo"], @@ -1041,7 +1063,7 @@ tests = , " bar |" , " || baz" ] =?> - table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] + table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)] [plain "", plain "baz"] [[plain "", plain "Foo"], [plain "", plain ""], @@ -1052,7 +1074,7 @@ tests = , " 4 | | 6" , " 7 | 8 | 9" ] =?> - table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0), (AlignDefault, 0.0)] + table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing), (AlignDefault, Nothing)] [] [[plain "1", plain "2", plain "3"], [plain "4", mempty, plain "6"], @@ -1063,7 +1085,7 @@ tests = , "| foo | bar |" , "+-----+-----+" ] =?> - table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] + table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)] [] [[para "foo", para "bar"]] , "Grid table inside list" =: @@ -1072,7 +1094,7 @@ tests = , " | foo | bar |" , " +-----+-----+" ] =?> - bulletList [table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] + bulletList [table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)] [] [[para "foo", para "bar"]]] , "Grid table with two rows" =: @@ -1083,7 +1105,7 @@ tests = , "| bat | baz |" , "+-----+-----+" ] =?> - table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] + table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)] [] [[para "foo", para "bar"] ,[para "bat", para "baz"]] @@ -1095,9 +1117,9 @@ tests = , "|+---+|" , "+-----+" ] =?> - table mempty [(AlignDefault, 0.0)] + table mempty [(AlignDefault, Nothing)] [] - [[table mempty [(AlignDefault, 0.0)] + [[table mempty [(AlignDefault, Nothing)] [] [[para "foo"]]]] , "Grid table with example" =: @@ -1108,7 +1130,7 @@ tests = , "| </example> |" , "+------------+" ] =?> - table mempty [(AlignDefault, 0.0)] + table mempty [(AlignDefault, Nothing)] [] [[codeBlock "foo"]] ] @@ -1479,13 +1501,13 @@ tests = ] , "Definition list with table" =: " foo :: bar | baz" =?> - definitionList [ ("foo", [ table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] + definitionList [ ("foo", [ table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)] [] [[plain "bar", plain "baz"]] ])] , "Definition list with table inside bullet list" =: " - foo :: bar | baz" =?> - bulletList [definitionList [ ("foo", [ table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)] + bulletList [definitionList [ ("foo", [ table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)] [] [[plain "bar", plain "baz"]] ])]] diff --git a/test/Tests/Readers/Org/Block/Table.hs b/test/Tests/Readers/Org/Block/Table.hs index e7e82d8d4..c09abcd0d 100644 --- a/test/Tests/Readers/Org/Block/Table.hs +++ b/test/Tests/Readers/Org/Block/Table.hs @@ -24,7 +24,7 @@ simpleTable' :: Int -> [Blocks] -> [[Blocks]] -> Blocks -simpleTable' n = table "" (replicate n (AlignDefault, 0.0)) +simpleTable' n = table "" (replicate n (AlignDefault, Nothing)) tests :: [TestTree] tests = @@ -121,7 +121,7 @@ tests = , "| 1 | One | foo |" , "| 2 | Two | bar |" ] =?> - table "" (zip [AlignCenter, AlignRight, AlignDefault] [0, 0, 0]) + table "" (zip [AlignCenter, AlignRight, AlignDefault] [Nothing, Nothing, Nothing]) [] [ [ plain "Numbers", plain "Text", plain "More" ] , [ plain "1" , plain "One" , plain "foo" ] @@ -143,7 +143,7 @@ tests = , "| 1 | One | foo |" , "| 2" ] =?> - table "" (zip [AlignCenter, AlignRight] [0, 0]) + table "" (zip [AlignCenter, AlignRight] [Nothing, Nothing]) [ plain "Numbers", plain "Text" ] [ [ plain "1" , plain "One" , plain "foo" ] , [ plain "2" ] @@ -155,7 +155,7 @@ tests = , "| 9 | 42 |" ] =?> table "Hitchhiker's Multiplication Table" - [(AlignDefault, 0), (AlignDefault, 0)] + [(AlignDefault, Nothing), (AlignDefault, Nothing)] [] [ [ plain "x", plain "6" ] , [ plain "9", plain "42" ] diff --git a/test/Tests/Readers/Txt2Tags.hs b/test/Tests/Readers/Txt2Tags.hs index f22d0f19f..e9ee6729c 100644 --- a/test/Tests/Readers/Txt2Tags.hs +++ b/test/Tests/Readers/Txt2Tags.hs @@ -44,7 +44,7 @@ simpleTable' :: Int -> [Blocks] -> [[Blocks]] -> Blocks -simpleTable' n = table "" (replicate n (AlignCenter, 0.0)) +simpleTable' n = table "" (replicate n (AlignCenter, Nothing)) tests :: [TestTree] tests = @@ -398,7 +398,7 @@ tests = , "| 1 | One | foo |" , "| 2 | Two | bar |" ] =?> - table "" (zip [AlignCenter, AlignRight, AlignDefault] [0, 0, 0]) + table "" (zip [AlignCenter, AlignRight, AlignDefault] [Nothing, Nothing, Nothing]) [] [ [ plain "Numbers", plain "Text", plain "More" ] , [ plain "1" , plain "One" , plain "foo" ] @@ -415,7 +415,7 @@ tests = , "| 1 | One | foo |" , "| 2 " ] =?> - table "" (zip [AlignCenter, AlignLeft, AlignLeft] [0, 0, 0]) + table "" (zip [AlignCenter, AlignLeft, AlignLeft] [Nothing, Nothing, Nothing]) [ plain "Numbers", plain "Text" , plain mempty ] [ [ plain "1" , plain "One" , plain "foo" ] , [ plain "2" , plain mempty , plain mempty ] diff --git a/test/Tests/Writers/ConTeXt.hs b/test/Tests/Writers/ConTeXt.hs index 082ff12fe..ea717b48e 100644 --- a/test/Tests/Writers/ConTeXt.hs +++ b/test/Tests/Writers/ConTeXt.hs @@ -98,8 +98,8 @@ tests = [ testGroup "inline code" ] , testGroup "natural tables" [ test contextNtb "table with header and caption" $ - let caption = text "Table 1" - aligns = [(AlignRight, 0.0), (AlignLeft, 0.0), (AlignCenter, 0.0), (AlignDefault, 0.0)] + let capt = text "Table 1" + aligns = [(AlignRight, Nothing), (AlignLeft, Nothing), (AlignCenter, Nothing), (AlignDefault, Nothing)] headers = [plain $ text "Right", plain $ text "Left", plain $ text "Center", @@ -116,7 +116,7 @@ tests = [ testGroup "inline code" plain $ text "3.2", plain $ text "3.3", plain $ text "3.4"]] - in table caption aligns headers rows + in table capt aligns headers rows =?> unlines [ "\\startplacetable[title={Table 1}]" , "\\startTABLE" , "\\startTABLEhead" diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs index ee61d18e0..ba5fdf94f 100644 --- a/test/Tests/Writers/Muse.hs +++ b/test/Tests/Writers/Muse.hs @@ -372,7 +372,7 @@ tests = [ testGroup "block elements" [ "table without header" =: let rows = [[para "Para 1.1", para "Para 1.2"] ,[para "Para 2.1", para "Para 2.2"]] - in table mempty [(AlignDefault,0.0),(AlignDefault,0.0)] + in table mempty [(AlignDefault,Nothing),(AlignDefault,Nothing)] [mempty, mempty] rows =?> unlines [ " Para 1.1 | Para 1.2" @@ -389,11 +389,11 @@ tests = [ testGroup "block elements" , " Para 2.1 | Para 2.2" ] , "table with header and caption" =: - let caption = "Table 1" + let capt = "Table 1" headers = [plain "header 1", plain "header 2"] rows = [[para "Para 1.1", para "Para 1.2"] ,[para "Para 2.1", para "Para 2.2"]] - in table caption [(AlignDefault,0.0),(AlignDefault,0.0)] + in table capt [(AlignDefault,Nothing),(AlignDefault,Nothing)] headers rows =?> unlines [ " header 1 || header 2" , " Para 1.1 | Para 1.2" diff --git a/test/command/1881.md b/test/command/1881.md index c0902de71..fabd6d94b 100644 --- a/test/command/1881.md +++ b/test/command/1881.md @@ -20,15 +20,27 @@ </tbody> </table> ^D -[Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."] [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 "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]]]]] +[Table ("",[],[]) (Caption Nothing + [Para [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."]]) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Right"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Center"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]]]] + []] ``` ``` @@ -42,14 +54,26 @@ </tr> </table> ^D -[Table [] [AlignRight,AlignLeft,AlignCenter,AlignRight] [0.0,0.0,0.0,0.0] - [[] - ,[] - ,[] - ,[]] - [[[Plain [Str "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]]]]] +[Table ("",[],[]) (Caption Nothing + []) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignRight,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]]]] + []] ``` diff --git a/test/command/3348.md b/test/command/3348.md index 6e0c07033..f21b4845d 100644 --- a/test/command/3348.md +++ b/test/command/3348.md @@ -7,11 +7,22 @@ line of text ----- ------------------------------------------------ ^D -[Table [] [AlignRight,AlignLeft] [8.333333333333333e-2,0.6805555555555556] - [[] - ,[]] - [[[Plain [Str "foo"]] - ,[Plain [Str "bar"]]] - ,[[Plain [Str "foo"]] - ,[Plain [Str "this",Space,Str "is",Space,Str "a",Space,Str "long",SoftBreak,Str "line",Space,Str "of",Space,Str "text"]]]]] +[Table ("",[],[]) (Caption Nothing + []) [(AlignRight,Just 8.333333333333333e-2),(AlignLeft,Just 0.6805555555555556)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "foo"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "bar"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "foo"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "this",Space,Str "is",Space,Str "a",Space,Str "long",SoftBreak,Str "line",Space,Str "of",Space,Str "text"]]]] + []] ``` diff --git a/test/command/3516.md b/test/command/3516.md index 8c7e478d3..602d8442b 100644 --- a/test/command/3516.md +++ b/test/command/3516.md @@ -24,24 +24,46 @@ on Windows builds. | | | +---+---+ ^D -[Table [] [AlignDefault,AlignDefault] [5.555555555555555e-2,5.555555555555555e-2] - [[] - ,[]] - [[[Plain [Str "1"]] - ,[Plain [Str "2"]]] - ,[[] - ,[]]]] +[Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Just 5.555555555555555e-2),(AlignDefault,Just 5.555555555555555e-2)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + []] ``` ``` % pandoc -f native -t rst -[Table [] [AlignDefault,AlignDefault] [5.555555555555555e-2,5.555555555555555e-2] - [[] - ,[]] - [[[Para [Str "1"]] - ,[Para [Str "2"]]] - ,[[] - ,[]]]] +[Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Just 5.555555555555555e-2),(AlignDefault,Just 5.555555555555555e-2)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "2"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + []] ^D +---+---+ | 1 | 2 | diff --git a/test/command/3533-rst-csv-tables.md b/test/command/3533-rst-csv-tables.md index 181462f7f..1fcf3bae9 100644 --- a/test/command/3533-rst-csv-tables.md +++ b/test/command/3533-rst-csv-tables.md @@ -5,16 +5,30 @@ :header: Flavor,Price,Slogan :file: command/3533-rst-csv-tables.csv ^D -[Table [Str "Test"] [AlignDefault,AlignDefault,AlignDefault] [0.4,0.2,0.4] - [[Plain [Str "Flavor"]] - ,[Plain [Str "Price"]] - ,[Plain [Str "Slogan"]]] - [[[Plain [Str "Albatross"]] - ,[Plain [Str "2.99"]] - ,[Plain [Str "On",Space,Str "a",Space,Str "stick!"]]] - ,[[Plain [Str "Crunchy",Space,Str "Frog"]] - ,[Plain [Str "1.49"]] - ,[Plain [Str "If",Space,Str "we",Space,Str "took",Space,Str "the",Space,Str "bones",Space,Str "out,",Space,Str "it",Space,Str "wouldn't",Space,Str "be",SoftBreak,Str "crunchy,",Space,Str "now",Space,Str "would",Space,Str "it?"]]]]] +[Table ("",[],[]) (Caption Nothing + [Para [Str "Test"]]) [(AlignDefault,Just 0.4),(AlignDefault,Just 0.2),(AlignDefault,Just 0.4)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Flavor"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Price"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Slogan"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Albatross"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2.99"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "On",Space,Str "a",Space,Str "stick!"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Crunchy",Space,Str "Frog"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1.49"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "If",Space,Str "we",Space,Str "took",Space,Str "the",Space,Str "bones",Space,Str "out,",Space,Str "it",Space,Str "wouldn't",Space,Str "be",SoftBreak,Str "crunchy,",Space,Str "now",Space,Str "would",Space,Str "it?"]]]] + []] ``` ``` @@ -28,16 +42,30 @@ 'cat''s' 3 4 'dog''s' 2 3 ^D -[Table [Str "Test"] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[] - ,[Plain [Str "a"]] - ,[Plain [Str "b"]]] - [[[Plain [Str "cat's"]] - ,[Plain [Str "3"]] - ,[Plain [Str "4"]]] - ,[[Plain [Str "dog's"]] - ,[Plain [Str "2"]] - ,[Plain [Str "3"]]]]] +[Table ("",[],[]) (Caption Nothing + [Para [Str "Test"]]) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "a"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "b"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "cat's"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "4"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "dog's"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3"]]]] + []] ``` ``` @@ -47,10 +75,18 @@ "1","\"" ^D -[Table [Str "Test"] [AlignDefault,AlignDefault] [0.0,0.0] - [[] - ,[]] - [[[Plain [Str "1"]] - ,[Plain [Str "\""]]]]] +[Table ("",[],[]) (Caption Nothing + [Para [Str "Test"]]) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "\""]]]] + []] ``` diff --git a/test/command/3706.md b/test/command/3706.md index 3765372fa..8430a929c 100644 --- a/test/command/3706.md +++ b/test/command/3706.md @@ -16,15 +16,29 @@ pandoc -f org -t native | 3 | La | ^D [Div ("tab",[],[]) - [Table [Str "Lalelu."] [AlignDefault,AlignDefault] [0.0,0.0] - [[Plain [Str "Id"]] - ,[Plain [Str "Desc"]]] - [[[Plain [Str "1"]] - ,[Plain [Str "La"]]] - ,[[Plain [Str "2"]] - ,[Plain [Str "La"]]] - ,[[Plain [Str "3"]] - ,[Plain [Str "La"]]]]]] + [Table ("",[],[]) (Caption Nothing + [Para [Str "Lalelu."]]) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Id"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Desc"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "La"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "La"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "La"]]]] + []]] ``` ``` diff --git a/test/command/3708.md b/test/command/3708.md index 2cbc82c25..1eb0c256a 100644 --- a/test/command/3708.md +++ b/test/command/3708.md @@ -5,11 +5,22 @@ C & D \end{tabular} ^D -[Table [] [AlignCenter,AlignCenter] [0.0,0.0] - [[] - ,[]] - [[[Plain [Str "A"]] - ,[Plain [Str "B&1"]]] - ,[[Plain [Str "C"]] - ,[Plain [Str "D"]]]]] +[Table ("",[],[]) (Caption Nothing + []) [(AlignCenter,Nothing),(AlignCenter,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "A"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "B&1"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "C"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "D"]]]] + []] ``` diff --git a/test/command/4056.md b/test/command/4056.md index e972931dd..bf02ec5f0 100644 --- a/test/command/4056.md +++ b/test/command/4056.md @@ -14,11 +14,21 @@ Blah & Foo & Bar \\ \end{tabular} ^D -[Table [] [AlignLeft,AlignRight,AlignRight] [0.0,0.0,0.0] - [[] - ,[] - ,[]] - [[[Plain [Str "Blah"]] - ,[Plain [Str "Foo"]] - ,[Plain [Str "Bar"]]]]] +[Table ("",[],[]) (Caption Nothing + []) [(AlignLeft,Nothing),(AlignRight,Nothing),(AlignRight,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Blah"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Foo"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Bar"]]]] + []] ``` diff --git a/test/command/4119.md b/test/command/4119.md index 70f008643..1df7775c8 100644 --- a/test/command/4119.md +++ b/test/command/4119.md @@ -8,11 +8,19 @@ pandoc -t native not a caption! :::::::::::::::: ^D -[Table [] [AlignDefault,AlignDefault] [0.0,0.0] - [[Plain [Str "col1"]] - ,[Plain [Str "col2"]]] - [[[Plain [Str "1"]] - ,[Plain [Str "2"]]]] +[Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "col1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "col2"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]]]] + [] ,Div ("",["notes"],[]) [Para [Str "not",Space,Str "a",Space,Str "caption!"]]] ``` diff --git a/test/command/4320.md b/test/command/4320.md index a205c9269..dc9b076d6 100644 --- a/test/command/4320.md +++ b/test/command/4320.md @@ -1,11 +1,19 @@ ``` % pandoc -f native -t rst --wrap=none -[Table [] [AlignDefault,AlignDefault] [0.3,0.3] - [[Plain [Str "one"]] - ,[Plain [Str "two"]]] - [[[Plain [Str "ports"]] - ,[BlockQuote - [Para [Strong [Str "thisIsGoingToBeTooLongAnyway"]]]]]]] +[Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Just 0.3),(AlignDefault,Just 0.3)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "one"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "two"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "ports"]] + ,Cell ("",[],[]) Nothing 1 1 + [BlockQuote + [Para [Strong [Str "thisIsGoingToBeTooLongAnyway"]]]]]] + []] ^D +--------------------+-------------------------------------+ | one | two | diff --git a/test/command/4513.md b/test/command/4513.md index e4a4406e4..e315d3820 100644 --- a/test/command/4513.md +++ b/test/command/4513.md @@ -2,8 +2,13 @@ % pandoc -f textile -t native |_. heading 1 |_. heading 2| ^D -[Table [] [AlignDefault,AlignDefault] [0.0,0.0] - [[Plain [Str "heading",Space,Str "1"]] - ,[Plain [Str "heading",Space,Str "2"]]] +[Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "heading",Space,Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "heading",Space,Str "2"]]]] + [] []] ``` diff --git a/test/command/4579.md b/test/command/4579.md index 80f0f58c2..6c01cf734 100644 --- a/test/command/4579.md +++ b/test/command/4579.md @@ -8,9 +8,17 @@ * - spam - ham ^D -[Table [] [AlignDefault,AlignDefault] [0.0,0.0] - [[Plain [Str "Foo"]] - ,[Plain [Str "Bar"]]] - [[[Plain [Str "spam"]] - ,[Plain [Str "ham"]]]]] +[Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Foo"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Bar"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "spam"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "ham"]]]] + []] ``` diff --git a/test/command/5014.md b/test/command/5014.md index c19490496..79cc99cd0 100644 --- a/test/command/5014.md +++ b/test/command/5014.md @@ -13,7 +13,13 @@ </tbody> </table> ^D -[Table [] [AlignDefault] [0.0] - [[Plain [Str "Name"]]] - [[[Plain [Str "Accounts"]]]]] +[Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Name"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Accounts"]]]] + []] ``` diff --git a/test/command/5079.md b/test/command/5079.md index aa93ae6f3..1a566d6e4 100644 --- a/test/command/5079.md +++ b/test/command/5079.md @@ -10,7 +10,13 @@ </tbody> </table> ^D -[Table [] [AlignDefault] [0.0] - [[]] - [[[Plain [Str "Cell"]]]]] +[Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell"]]]] + []] ``` diff --git a/test/command/5708.md b/test/command/5708.md index 00a98a371..f104c30c3 100644 --- a/test/command/5708.md +++ b/test/command/5708.md @@ -4,9 +4,17 @@ | 123456 | :math:`a + b` | +--------+----------------+ ^D -[Table [] [AlignDefault,AlignDefault] [0.125,0.2361111111111111] - [[] - ,[]] - [[[Plain [Str "123456"]] - ,[Plain [Math InlineMath "a + b"]]]]] +[Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Just 0.125),(AlignDefault,Just 0.2361111111111111)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123456"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Math InlineMath "a + b"]]]] + []] ``` diff --git a/test/command/5711.md b/test/command/5711.md index 0d443c656..2e45d5fa1 100644 --- a/test/command/5711.md +++ b/test/command/5711.md @@ -7,7 +7,13 @@ \end{tabular} \end{document} ^D -[Table [] [AlignCenter] [0.0] - [[]] - [[[Plain [Str "d",LineBreak,Str "e"]]]]] +[Table ("",[],[]) (Caption Nothing + []) [(AlignCenter,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "d",LineBreak,Str "e"]]]] + []] ``` diff --git a/test/command/6137.md b/test/command/6137.md index c1e0ac01c..4dcc0fe8f 100644 --- a/test/command/6137.md +++ b/test/command/6137.md @@ -17,16 +17,30 @@ This reference to Figure \ref{fig:label} works fine. ^D [Para [Str "This",Space,Str "reference",Space,Str "to",Space,Str "Table",Space,Link ("",[],[("reference-type","ref"),("reference","tbl:label")]) [Str "1"] ("#tbl:label",""),Space,Str "doesn\8217t",Space,Str "work."] ,Div ("tbl:label",[],[]) - [Table [Str "This",Space,Str "caption",Space,Str "has",Space,Str "no",Space,Str "number."] [AlignLeft,AlignCenter,AlignRight] [0.0,0.0,0.0] - [[] - ,[] - ,[]] - [[[Plain [Str "\8212\8212\8211"]] - ,[Plain [Str "\8212\8212\8211"]] - ,[Plain [Str "\8212\8212\8211"]]] - ,[[Plain [Str "\8212\8212\8211"]] - ,[Plain [Str "\8212\8212\8211"]] - ,[Plain [Str "\8212\8212\8211"]]]]] + [Table ("",[],[]) (Caption Nothing + [Para [Str "This",Space,Str "caption",Space,Str "has",Space,Str "no",Space,Str "number."]]) [(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignRight,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "\8212\8212\8211"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "\8212\8212\8211"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "\8212\8212\8211"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "\8212\8212\8211"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "\8212\8212\8211"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "\8212\8212\8211"]]]] + []] ,Para [Str "This",Space,Str "reference",Space,Str "to",Space,Str "Figure",Space,Link ("",[],[("reference-type","ref"),("reference","fig:label")]) [Str "1"] ("#fig:label",""),Space,Str "works",Space,Str "fine."] ,Para [Image ("fig:label",[],[("width","\\textwidth")]) [Str "A",Space,Str "numbered",Space,Str "caption,",Space,Str "if",Space,Str "I",Space,Str "use",Space,Str "pandoc-crossref."] ("example.png","fig:")]] ``` diff --git a/test/command/csv.md b/test/command/csv.md index 4d38572f1..d633840fd 100644 --- a/test/command/csv.md +++ b/test/command/csv.md @@ -5,17 +5,35 @@ Apple,25 cents,33 """Navel"" Orange","35 cents",22 ,,45 ^D -[Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[Plain [Str "Fruit"]] - ,[Plain [Str "Price"]] - ,[Plain [Str "Quantity"]]] - [[[Plain [Str "Apple"]] - ,[Plain [Str "25",Space,Str "cents"]] - ,[Plain [Str "33"]]] - ,[[Plain [Str "\"Navel\"",Space,Str "Orange"]] - ,[Plain [Str "35",Space,Str "cents"]] - ,[Plain [Str "22"]]] - ,[[] - ,[] - ,[Plain [Str "45"]]]]] +[Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Fruit"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Price"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Quantity"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Apple"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "25",Space,Str "cents"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "33"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "\"Navel\"",Space,Str "Orange"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "35",Space,Str "cents"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "22"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "45"]]]] + []] ``` diff --git a/test/command/gfm.md b/test/command/gfm.md index a4bb088b6..3ef3665a6 100644 --- a/test/command/gfm.md +++ b/test/command/gfm.md @@ -7,13 +7,24 @@ gfm tests: | apple | 0.13 | | orange|1.12| ^D -[Table [] [AlignDefault,AlignRight] [0.0,0.0] - [[Plain [Str "Fruit"]] - ,[Plain [Str "Price"]]] - [[[Plain [Str "apple"]] - ,[Plain [Str "0.13"]]] - ,[[Plain [Str "orange"]] - ,[Plain [Str "1.12"]]]]] +[Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignRight,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Fruit"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Price"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "apple"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "0.13"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "orange"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1.12"]]]] + []] ``` ``` @@ -57,13 +68,24 @@ My:thumbsup:emoji:heart: ``` % pandoc -t gfm -f native -[Table [Str "The",Space,Str "caption."] [AlignDefault,AlignRight] [0.0,0.0] - [[Plain [Str "Fruit"]] - ,[Plain [Str "Price"]]] - [[[Plain [Str "apple"]] - ,[Plain [Str "0.13"]]] - ,[[Plain [Str "orange"]] - ,[Plain [Str "1.12"]]]]] +[Table ("",[],[]) (Caption Nothing + [Para [Str "The",Space,Str "caption."]]) [(AlignDefault,Nothing),(AlignRight,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Fruit"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Price"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "apple"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "0.13"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "orange"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1.12"]]]] + []] ^D | Fruit | Price | | ------ | ----: | diff --git a/test/command/latex-tabular-column-specs.md b/test/command/latex-tabular-column-specs.md index ed44a9980..65835019f 100644 --- a/test/command/latex-tabular-column-specs.md +++ b/test/command/latex-tabular-column-specs.md @@ -11,14 +11,28 @@ f & 0.5 & 5,5 \\ \bottomrule \end{tabular} ^D -[Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0] - [[Plain [Math InlineMath ""]] - ,[Plain [Math InlineMath "f1"]] - ,[Plain [Math InlineMath "f2"]]] - [[[Plain [Math InlineMath "e"]] - ,[Plain [Math InlineMath "0.5"]] - ,[Plain [Math InlineMath "4"]]] - ,[[Plain [Math InlineMath "f"]] - ,[Plain [Math InlineMath "0.5"]] - ,[Plain [Math InlineMath "5,5"]]]]] +[Table ("",[],[]) (Caption Nothing + []) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Math InlineMath ""]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Math InlineMath "f1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Math InlineMath "f2"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Math InlineMath "e"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Math InlineMath "0.5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Math InlineMath "4"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Math InlineMath "f"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Math InlineMath "0.5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Math InlineMath "5,5"]]]] + []] ``` diff --git a/test/command/tabularx.md b/test/command/tabularx.md index bf7670e9c..9ed991713 100644 --- a/test/command/tabularx.md +++ b/test/command/tabularx.md @@ -6,33 +6,51 @@ & Column Heading 2 & Column Heading 3 \\ \hline - Cell 1.1 + Cell 1.1 & Cell 1.2 & Cell 1.3 \\ \hline - Cell 2.1 + Cell 2.1 & Cell 2.2 & Cell 2.3 \\ \hline - Cell 3.1 + Cell 3.1 & Cell 3.2 & Cell 3.3 \\ \hline \end{tabularx} ^D -[Table [] [AlignCenter,AlignCenter,AlignCenter] [0.0,0.0,0.0] - [[Plain [Str "Column",Space,Str "Heading",Space,Str "1"]] - ,[Plain [Str "Column",Space,Str "Heading",Space,Str "2"]] - ,[Plain [Str "Column",Space,Str "Heading",Space,Str "3"]]] - [[[Plain [Str "Cell",Space,Str "1.1"]] - ,[Plain [Str "Cell",Space,Str "1.2"]] - ,[Plain [Str "Cell",Space,Str "1.3"]]] - ,[[Plain [Str "Cell",Space,Str "2.1"]] - ,[Plain [Str "Cell",Space,Str "2.2"]] - ,[Plain [Str "Cell",Space,Str "2.3"]]] - ,[[Plain [Str "Cell",Space,Str "3.1"]] - ,[Plain [Str "Cell",Space,Str "3.2"]] - ,[Plain [Str "Cell",Space,Str "3.3"]]]]] +[Table ("",[],[]) (Caption Nothing + []) [(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Column",Space,Str "Heading",Space,Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Column",Space,Str "Heading",Space,Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Column",Space,Str "Heading",Space,Str "3"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "1.1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "1.2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "1.3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "2.1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "2.2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "2.3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "3.1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "3.2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "3.3"]]]] + []] ``` ``` @@ -43,33 +61,51 @@ & Column Heading 2 & Column Heading 3 \\ \hline - Cell 1.1 + Cell 1.1 & Cell 1.2 & Cell 1.3 \\ \hline - Cell 2.1 + Cell 2.1 & Cell 2.2 & Cell 2.3 \\ \hline - Cell 3.1 + Cell 3.1 & Cell 3.2 & Cell 3.3 \\ \hline \end{tabularx} ^D -[Table [] [AlignLeft,AlignCenter,AlignLeft] [0.0,0.0,0.25] - [[Plain [Str "Column",Space,Str "Heading",Space,Str "1"]] - ,[Plain [Str "Column",Space,Str "Heading",Space,Str "2"]] - ,[Plain [Str "Column",Space,Str "Heading",Space,Str "3"]]] - [[[Plain [Str "Cell",Space,Str "1.1"]] - ,[Plain [Str "Cell",Space,Str "1.2"]] - ,[Plain [Str "Cell",Space,Str "1.3"]]] - ,[[Plain [Str "Cell",Space,Str "2.1"]] - ,[Plain [Str "Cell",Space,Str "2.2"]] - ,[Plain [Str "Cell",Space,Str "2.3"]]] - ,[[Plain [Str "Cell",Space,Str "3.1"]] - ,[Plain [Str "Cell",Space,Str "3.2"]] - ,[Plain [Str "Cell",Space,Str "3.3"]]]]] +[Table ("",[],[]) (Caption Nothing + []) [(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignLeft,Just 0.25)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Column",Space,Str "Heading",Space,Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Column",Space,Str "Heading",Space,Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Column",Space,Str "Heading",Space,Str "3"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "1.1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "1.2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "1.3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "2.1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "2.2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "2.3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "3.1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "3.2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "3.3"]]]] + []] ``` ``` @@ -80,31 +116,49 @@ & Column Heading 2 & Column Heading 3 \\ \hline - Cell 1.1 + Cell 1.1 & Cell 1.2 & Cell 1.3 \\ \hline - Cell 2.1 + Cell 2.1 & Cell 2.2 & Cell 2.3 \\ \hline - Cell 3.1 + Cell 3.1 & Cell 3.2 & Cell 3.3 \\ \hline \end{tabularx} ^D -[Table [] [AlignLeft,AlignCenter,AlignLeft] [0.25,0.0,0.25] - [[Plain [Str "Column",Space,Str "Heading",Space,Str "1"]] - ,[Plain [Str "Column",Space,Str "Heading",Space,Str "2"]] - ,[Plain [Str "Column",Space,Str "Heading",Space,Str "3"]]] - [[[Plain [Str "Cell",Space,Str "1.1"]] - ,[Plain [Str "Cell",Space,Str "1.2"]] - ,[Plain [Str "Cell",Space,Str "1.3"]]] - ,[[Plain [Str "Cell",Space,Str "2.1"]] - ,[Plain [Str "Cell",Space,Str "2.2"]] - ,[Plain [Str "Cell",Space,Str "2.3"]]] - ,[[Plain [Str "Cell",Space,Str "3.1"]] - ,[Plain [Str "Cell",Space,Str "3.2"]] - ,[Plain [Str "Cell",Space,Str "3.3"]]]]] +[Table ("",[],[]) (Caption Nothing + []) [(AlignLeft,Just 0.25),(AlignCenter,Nothing),(AlignLeft,Just 0.25)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Column",Space,Str "Heading",Space,Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Column",Space,Str "Heading",Space,Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Column",Space,Str "Heading",Space,Str "3"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "1.1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "1.2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "1.3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "2.1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "2.2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "2.3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "3.1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "3.2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "3.3"]]]] + []] ``` diff --git a/test/creole-reader.native b/test/creole-reader.native index a7e85d969..f9e0f6d28 100644 --- a/test/creole-reader.native +++ b/test/creole-reader.native @@ -69,25 +69,50 @@ Pandoc (Meta {unMeta = fromList []}) ,Para [Image ("",[],[]) [Str "here is a red flower"] ("Red-Flower.jpg","")] ,Header 3 ("",[],[]) [Str "Creole 0.4"] ,Para [Str "Tables",Space,Str "are",Space,Str "done",Space,Str "like",Space,Str "this:"] -,Table [] [AlignDefault,AlignDefault] [0.0,0.0] - [[Plain [Str "header",Space,Str "col1"]] - ,[Plain [Str "header",Space,Str "col2"]]] - [[[Plain [Str "col1"]] - ,[Plain [Str "col2"]]] - ,[[Plain [Str "you"]] - ,[Plain [Str "can"]]] - ,[[Plain [Str "also"]] - ,[Plain [Str "align",LineBreak,Str "it."]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "header",Space,Str "col1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "header",Space,Str "col2"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "col1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "col2"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "you"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "can"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "also"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "align",LineBreak,Str "it."]]]] + [] ,Para [Str "You",Space,Str "can",Space,Str "format",Space,Str "an",Space,Str "address",Space,Str "by",Space,Str "simply",Space,Str "forcing",Space,Str "linebreaks:"] ,Para [Str "My",Space,Str "contact",Space,Str "dates:",LineBreak,Str "Pone:",Space,Str "xyz",LineBreak,Str "Fax:",Space,Str "+45",LineBreak,Str "Mobile:",Space,Str "abc"] ,Header 3 ("",[],[]) [Str "Creole 0.5"] -,Table [] [AlignDefault,AlignDefault] [0.0,0.0] - [[Plain [Str "Header",Space,Str "title"]] - ,[Plain [Str "Another",Space,Str "header",Space,Str "title"]]] - [[[Plain [Code ("",[],[]) " //not italic text// "]] - ,[Plain [Code ("",[],[]) " **not bold text** "]]] - ,[[Plain [Emph [Str "italic",Space,Str "text"]]] - ,[Plain [Strong [Space,Str "bold",Space,Str "text",Space]]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Header",Space,Str "title"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Another",Space,Str "header",Space,Str "title"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Code ("",[],[]) " //not italic text// "]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Code ("",[],[]) " **not bold text** "]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Emph [Str "italic",Space,Str "text"]]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Strong [Space,Str "bold",Space,Str "text",Space]]]]] + [] ,Header 3 ("",[],[]) [Str "Creole 1.0"] ,Para [Str "If",Space,Str "interwiki",Space,Str "links",Space,Str "are",Space,Str "setup",Space,Str "in",Space,Str "your",Space,Str "wiki,",Space,Str "this",Space,Str "links",Space,Str "to",Space,Str "the",Space,Str "WikiCreole",Space,Str "page",Space,Str "about",Space,Str "Creole",Space,Str "1.0",Space,Str "test",Space,Str "cases:",Space,Link ("",[],[]) [Str "WikiCreole:Creole1.0TestCases"] ("WikiCreole:Creole1.0TestCases",""),Str "."] ,HorizontalRule diff --git a/test/docbook-reader.native b/test/docbook-reader.native index 3cce889f6..5ca83cf2e 100644 --- a/test/docbook-reader.native +++ b/test/docbook-reader.native @@ -282,116 +282,255 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Sof ,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."] ,Header 1 ("tables",[],[]) [Str "Tables"] ,Para [Str "Simple",Space,Str "table",Space,Str "with",Space,Str "caption:"] -,Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."] [AlignRight,AlignLeft,AlignCenter,AlignLeft] [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 "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]]] - ,[[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]]] - ,[[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]]]] +,Table ("",[],[]) (Caption Nothing + [Para [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."]]) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignLeft,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Right"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Center"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]]]] + [] ,Para [Str "Simple",Space,Str "table",Space,Str "without",Space,Str "caption:"] -,Table [] [AlignRight,AlignLeft,AlignCenter,AlignLeft] [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 "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]]] - ,[[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]]] - ,[[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignLeft,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Right"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Center"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]]]] + [] ,Para [Str "Simple",Space,Str "table",Space,Str "indented",Space,Str "two",Space,Str "spaces:"] -,Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."] [AlignRight,AlignLeft,AlignCenter,AlignLeft] [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 "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]]] - ,[[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]]] - ,[[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]]]] +,Table ("",[],[]) (Caption Nothing + [Para [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."]]) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignLeft,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Right"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Center"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]]]] + [] ,Para [Str "Multiline",Space,Str "table",Space,Str "with",Space,Str "caption:"] -,Table [Str "Here's",Space,Str "the",Space,Str "caption.",Space,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.2,0.2,0.3,0.3] - [[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 "row"]] - ,[Plain [Str "12.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."]]] - ,[[Plain [Str "Second"]] - ,[Plain [Str "row"]] - ,[Plain [Str "5.0"]] - ,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]] +,Table ("",[],[]) (Caption Nothing + [Para [Str "Here's",Space,Str "the",Space,Str "caption.",Space,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."]]) [(AlignCenter,Just 0.2),(AlignLeft,Just 0.2),(AlignRight,Just 0.3),(AlignLeft,Just 0.3)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Centered",Space,Str "Header"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left",Space,Str "Aligned"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Right",Space,Str "Aligned"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default",Space,Str "aligned"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "First"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "row"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12.0"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines."]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Second"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "row"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5.0"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]] + [] ,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "caption:"] -,Table [] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.1,0.2,0.3,0.4] - [[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 "row"]] - ,[Plain [Str "12.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."]]] - ,[[Plain [Str "Second"]] - ,[Plain [Str "row"]] - ,[Plain [Str "5.0"]] - ,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignCenter,Just 0.1),(AlignLeft,Just 0.2),(AlignRight,Just 0.3),(AlignLeft,Just 0.4)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Centered",Space,Str "Header"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left",Space,Str "Aligned"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Right",Space,Str "Aligned"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default",Space,Str "aligned"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "First"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "row"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12.0"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines."]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Second"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "row"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5.0"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]] + [] ,Para [Str "Table",Space,Str "without",Space,Str "column",Space,Str "headers:"] -,Table [] [AlignRight,AlignLeft,AlignCenter,AlignRight] [0.0,0.0,0.0,0.0] - [[] - ,[] - ,[] - ,[]] - [[[Plain [Str "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]]] - ,[[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]]] - ,[[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignRight,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]]]] + [] ,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "column",Space,Str "headers:"] -,Table [] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.25,0.25,0.25,0.25] - [[] - ,[] - ,[] - ,[]] - [[[Plain [Str "First"]] - ,[Plain [Str "row"]] - ,[Plain [Str "12.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."]]] - ,[[Plain [Str "Second"]] - ,[Plain [Str "row"]] - ,[Plain [Str "5.0"]] - ,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignCenter,Just 0.25),(AlignLeft,Just 0.25),(AlignRight,Just 0.25),(AlignLeft,Just 0.25)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "First"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "row"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12.0"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines."]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Second"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "row"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5.0"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]] + []] diff --git a/test/docx/0_level_headers.native b/test/docx/0_level_headers.native index 6d8269b21..3ee60c2f4 100644 --- a/test/docx/0_level_headers.native +++ b/test/docx/0_level_headers.native @@ -1,15 +1,39 @@ -[Table [] [AlignDefault] [0.0] - [[]] - [[[]] - ,[[Plain [Str "User\8217s",Space,Str "Guide"]]] - ,[[]] - ,[[]] - ,[[]] - ,[[Plain [Str "11",Space,Str "August",Space,Str "2017"]]] - ,[[]] - ,[[]] - ,[[]] - ,[[]]] +[Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "User\8217s",Space,Str "Guide"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "11",Space,Str "August",Space,Str "2017"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + []]] + [] ,Para [Str "CONTENTS"] ,Para [Strong [Str "Section",Space,Str "Page"]] ,Para [Str "FIGURES",Space,Str "iv"] diff --git a/test/docx/sdt_elements.native b/test/docx/sdt_elements.native index 7f7768728..ad48dab5c 100644 --- a/test/docx/sdt_elements.native +++ b/test/docx/sdt_elements.native @@ -1,10 +1,24 @@ -[Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[] - ,[] - ,[]] - [[[Plain [Strong [Str "col1Header"]]] - ,[Plain [Strong [Str "col2Header"]]] - ,[Plain [Strong [Str "col3Header"]]]] - ,[[Plain [Str "col1",Space,Str "content"]] - ,[Plain [Str "Body",Space,Str "copy"]] - ,[Plain [Str "col3",Space,Str "content"]]]]] +[Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Strong [Str "col1Header"]]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Strong [Str "col2Header"]]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Strong [Str "col3Header"]]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "col1",Space,Str "content"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Body",Space,Str "copy"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "col3",Space,Str "content"]]]] + []] diff --git a/test/docx/table_one_row.native b/test/docx/table_one_row.native index 1ea1b446c..36073641a 100644 --- a/test/docx/table_one_row.native +++ b/test/docx/table_one_row.native @@ -1,7 +1,17 @@ -[Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[] - ,[] - ,[]] - [[[Plain [Str "One"]] - ,[Plain [Str "Row"]] - ,[Plain [Str "Table"]]]]] +[Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "One"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Row"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Table"]]]] + []] diff --git a/test/docx/table_variable_width.native b/test/docx/table_variable_width.native index b85e58d41..0c6174937 100644 --- a/test/docx/table_variable_width.native +++ b/test/docx/table_variable_width.native @@ -1,16 +1,37 @@ -[Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0,0.0,0.0] - [[] - ,[] - ,[Plain [Str "h3"]] - ,[Plain [Str "h4"]] - ,[Plain [Str "h5"]]] - [[[Plain [Str "c11"]] - ,[] - ,[] - ,[] - ,[]] - ,[[] - ,[Plain [Str "c22"]] - ,[Plain [Str "c23"]] - ,[] - ,[]]]] + +[Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "h3"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "h4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "h5"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "c11"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "c22"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "c23"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + []]
\ No newline at end of file diff --git a/test/docx/table_with_list_cell.native b/test/docx/table_with_list_cell.native index 81bb15a1e..cc7b08a5e 100644 --- a/test/docx/table_with_list_cell.native +++ b/test/docx/table_with_list_cell.native @@ -1,11 +1,19 @@ -[Table [] [AlignDefault,AlignDefault] [0.0,0.0] - [[Plain [Str "Cell",Space,Str "with",Space,Str "text"]] - ,[Plain [Str "Cell",Space,Str "with",Space,Str "text"]]] - [[[BulletList +[Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "with",Space,Str "text"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "with",Space,Str "text"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [BulletList [[Para [Str "Cell",Space,Str "with"]] ,[Para [Str "A"]] ,[Para [Str "Bullet",Space,Str "list"]]]] - ,[OrderedList (1,Decimal,Period) + ,Cell ("",[],[]) Nothing 1 1 + [OrderedList (1,Decimal,Period) [[Para [Str "Cell",Space,Str "with"]] ,[Para [Str "A"]] - ,[Para [Str "Numbered",Space,Str "list."]]]]]]] + ,[Para [Str "Numbered",Space,Str "list."]]]]]] + []] diff --git a/test/docx/tables.native b/test/docx/tables.native index ae326950a..48de6f947 100644 --- a/test/docx/tables.native +++ b/test/docx/tables.native @@ -1,36 +1,80 @@ [Header 2 ("a-table-with-and-without-a-header-row",[],[]) [Str "A",Space,Str "table,",Space,Str "with",Space,Str "and",Space,Str "without",Space,Str "a",Space,Str "header",Space,Str "row"] -,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0,0.0] - [[Plain [Str "Name"]] - ,[Plain [Str "Game"]] - ,[Plain [Str "Fame"]] - ,[Plain [Str "Blame"]]] - [[[Plain [Str "Lebron",Space,Str "James"]] - ,[Plain [Str "Basketball"]] - ,[Plain [Str "Very",Space,Str "High"]] - ,[Plain [Str "Leaving",Space,Str "Cleveland"]]] - ,[[Plain [Str "Ryan",Space,Str "Braun"]] - ,[Plain [Str "Baseball"]] - ,[Plain [Str "Moderate"]] - ,[Plain [Str "Steroids"]]] - ,[[Plain [Str "Russell",Space,Str "Wilson"]] - ,[Plain [Str "Football"]] - ,[Plain [Str "High"]] - ,[Plain [Str "Tacky",Space,Str "uniform"]]]] -,Table [] [AlignDefault,AlignDefault] [0.0,0.0] - [[] - ,[]] - [[[Plain [Str "Sinple"]] - ,[Plain [Str "Table"]]] - ,[[Plain [Str "Without"]] - ,[Plain [Str "Header"]]]] -,Table [] [AlignDefault,AlignDefault] [0.0,0.0] - [[] - ,[]] - [[[Para [Str "Simple"] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Name"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Game"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Fame"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Blame"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Lebron",Space,Str "James"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Basketball"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Very",Space,Str "High"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Leaving",Space,Str "Cleveland"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Ryan",Space,Str "Braun"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Baseball"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Moderate"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Steroids"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Russell",Space,Str "Wilson"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Football"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "High"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Tacky",Space,Str "uniform"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Sinple"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Table"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Without"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Header"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "Simple"] ,Para [Str "Multiparagraph"]] - ,[Para [Str "Table"] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Table"] ,Para [Str "Full"]]] - ,[[Para [Str "Of"] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "Of"] ,Para [Str "Paragraphs"]] - ,[Para [Str "In",Space,Str "each"] - ,Para [Str "Cell."]]]]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "In",Space,Str "each"] + ,Para [Str "Cell."]]]] + []] diff --git a/test/dokuwiki_multiblock_table.native b/test/dokuwiki_multiblock_table.native index 6059efb71..677f0bc6d 100644 --- a/test/dokuwiki_multiblock_table.native +++ b/test/dokuwiki_multiblock_table.native @@ -1,18 +1,34 @@ -[Table [Str "Sample",Space,Str "grid",Space,Str "table."] [AlignDefault,AlignDefault,AlignDefault] [0.2222222222222222,0.2222222222222222,0.2916666666666667] - [[Plain [Str "Fruit"]] - ,[Plain [Str "Price"]] - ,[Plain [Str "Advantages"]]] - [[[Para [Str "Bananas"]] - ,[Para [Str "$1.34"]] - ,[Para [Str "built-in",Space,Str "wrapper"] +[Table ("",[],[]) (Caption Nothing + [Para [Str "Sample",Space,Str "grid",Space,Str "table."]]) [(AlignDefault,Just 0.2222222222222222),(AlignDefault,Just 0.2222222222222222),(AlignDefault,Just 0.2916666666666667)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Fruit"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Price"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Advantages"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "Bananas"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "$1.34"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "built-in",Space,Str "wrapper"] ,Para [Str "potassium"]]] - ,[[Para [Str "Oranges"]] - ,[Para [Str "$2.10"]] - ,[BulletList + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "Oranges"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "$2.10"]] + ,Cell ("",[],[]) Nothing 1 1 + [BulletList [[Plain [Str "cures",Space,Str "scurvy"]] ,[Plain [Str "tasty"]]]]] - ,[[Para [Str "Apples"]] - ,[Para [Str "$1.10"]] - ,[Para [Str "Some",Space,Str "text",LineBreak,LineBreak,Str "after",Space,Str "two",Space,Str "linebreaks"] - ]] - ]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "Apples"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "$1.10"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Some",Space,Str "text",LineBreak,LineBreak,Str "after",Space,Str "two",Space,Str "linebreaks"]]]] + []] diff --git a/test/html-reader.native b/test/html-reader.native index 5643fb73f..fe37927f1 100644 --- a/test/html-reader.native +++ b/test/html-reader.native @@ -331,147 +331,329 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl ,Para [Emph [Str "Trailing",Space,Str "spaces"],Space,Str "text"] ,Header 1 ("tables",[],[]) [Str "Tables"] ,Header 2 ("tables-with-headers",[],[]) [Str "Tables",Space,Str "with",Space,Str "Headers"] -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[Plain [Str "X"]] - ,[Plain [Str "Y"]] - ,[Plain [Str "Z"]]] - [[[Plain [Str "1"]] - ,[Plain [Str "2"]] - ,[Plain [Str "3"]]] - ,[[Plain [Str "4"]] - ,[Plain [Str "5"]] - ,[Plain [Str "6"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "X"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Y"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Z"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "6"]]]] + [] ,HorizontalRule -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[Plain [Str "X"]] - ,[Plain [Str "Y"]] - ,[Plain [Str "Z"]]] - [[[Plain [Str "1"]] - ,[Plain [Str "2"]] - ,[Plain [Str "3"]]] - ,[[Plain [Str "4"]] - ,[Plain [Str "5"]] - ,[Plain [Str "6"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "X"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Y"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Z"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "6"]]]] + [] ,HorizontalRule -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[Plain [Str "X"]] - ,[Plain [Str "Y"]] - ,[Plain [Str "Z"]]] - [[[Plain [Str "1"]] - ,[Plain [Str "2"]] - ,[Plain [Str "3"]]] - ,[[Plain [Str "4"]] - ,[Plain [Str "5"]] - ,[Plain [Str "6"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "X"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Y"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Z"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "6"]]]] + [] ,HorizontalRule -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[Plain [Str "X"]] - ,[Plain [Str "Y"]] - ,[Plain [Str "Z"]]] - [[[Plain [Str "1"]] - ,[Plain [Str "2"]] - ,[Plain [Str "3"]]] - ,[[Plain [Str "4"]] - ,[Plain [Str "5"]] - ,[Plain [Str "6"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "X"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Y"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Z"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "6"]]]] + [] ,HorizontalRule -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[Plain [Str "X"]] - ,[Plain [Str "Y"]] - ,[Plain [Str "Z"]]] - [[[Plain [Str "1"]] - ,[Plain [Str "2"]] - ,[Plain [Str "3"]]] - ,[[Plain [Str "4"]] - ,[Plain [Str "5"]] - ,[Plain [Str "6"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "X"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Y"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Z"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "6"]]]] + [] ,HorizontalRule -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[Plain [Str "X"]] - ,[Plain [Str "Y"]] - ,[Plain [Str "Z"]]] - [[[Plain [Str "1"]] - ,[Plain [Str "2"]] - ,[Plain [Str "3"]]] - ,[[Plain [Str "4"]] - ,[Plain [Str "5"]] - ,[Plain [Str "6"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "X"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Y"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Z"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "6"]]]] + [] ,HorizontalRule -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[Plain [Str "X"]] - ,[Plain [Str "Y"]] - ,[Plain [Str "Z"]]] - [[[Plain [Str "1"]] - ,[Plain [Str "2"]] - ,[Plain [Str "3"]]] - ,[[Plain [Str "4"]] - ,[Plain [Str "5"]] - ,[Plain [Str "6"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "X"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Y"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Z"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "6"]]]] + [] ,HorizontalRule -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[Plain [Str "X"]] - ,[Plain [Str "Y"]] - ,[Plain [Str "Z"]]] - [[[Plain [Str "1"]] - ,[Plain [Str "2"]] - ,[Plain [Str "3"]]] - ,[[Plain [Str "4"]] - ,[Plain [Str "5"]] - ,[Plain [Str "6"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "X"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Y"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Z"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "6"]]]] + [] ,HorizontalRule -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[Plain [Str "X"]] - ,[Plain [Str "Y"]] - ,[Plain [Str "Z"]]] - [[[Plain [Str "1"]] - ,[Para [Str "2"]] - ,[Plain [Str "3"]]] - ,[[Plain [Str "4"]] - ,[Plain [Str "5"]] - ,[Plain [Str "6"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "X"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Y"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Z"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "6"]]]] + [] ,Header 2 ("tables-without-headers",[],[]) [Str "Tables",Space,Str "without",Space,Str "Headers"] -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[] - ,[] - ,[]] - [[[Plain [Str "1"]] - ,[Plain [Str "2"]] - ,[Plain [Str "3"]]] - ,[[Plain [Str "4"]] - ,[Plain [Str "5"]] - ,[Plain [Str "6"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "6"]]]] + [] ,HorizontalRule -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[] - ,[] - ,[]] - [[[Plain [Str "1"]] - ,[Plain [Str "2"]] - ,[Plain [Str "3"]]] - ,[[Plain [Str "4"]] - ,[Plain [Str "5"]] - ,[Plain [Str "6"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "6"]]]] + [] ,HorizontalRule -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[] - ,[] - ,[]] - [[[Plain [Str "1"]] - ,[Plain [Str "2"]] - ,[Plain [Str "3"]]] - ,[[Plain [Str "4"]] - ,[Plain [Str "5"]] - ,[Plain [Str "6"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "6"]]]] + [] ,HorizontalRule -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[] - ,[] - ,[]] - [[[Plain [Str "1"]] - ,[Plain [Str "2"]] - ,[Plain [Str "3"]]] - ,[[Plain [Str "4"]] - ,[Plain [Str "5"]] - ,[Plain [Str "6"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "6"]]]] + [] ,Header 2 ("empty-tables",[],[]) [Str "Empty",Space,Str "Tables"] ,Para [Str "This",Space,Str "section",Space,Str "should",Space,Str "be",Space,Str "empty."]] diff --git a/test/jats-reader.native b/test/jats-reader.native index 83feeeffd..61dc0b483 100644 --- a/test/jats-reader.native +++ b/test/jats-reader.native @@ -287,136 +287,318 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,Para [Emph [Str "Trailing",Space,Str "spaces"],Space,Str "text"] ,Header 1 ("tables",[],[]) [Str "Tables"] ,Header 2 ("tables-with-headers",[],[]) [Str "Tables",Space,Str "with",Space,Str "Headers"] -,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0] - [[Para [Str "X"]] - ,[Para [Str "Y"]] - ,[Para [Str "Z"]]] - [[[Para [Str "1"]] - ,[Para [Str "2"]] - ,[Para [Str "3"]]] - ,[[Para [Str "4"]] - ,[Para [Str "5"]] - ,[Para [Str "6"]]]] -,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0] - [[Para [Str "X"]] - ,[Para [Str "Y"]] - ,[Para [Str "Z"]]] - [[[Para [Str "1"]] - ,[Para [Str "2"]] - ,[Para [Str "3"]]] - ,[[Para [Str "4"]] - ,[Para [Str "5"]] - ,[Para [Str "6"]]]] -,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0] - [[Para [Str "X"]] - ,[Para [Str "Y"]] - ,[Para [Str "Z"]]] - [[[Para [Str "1"]] - ,[Para [Str "2"]] - ,[Para [Str "3"]]] - ,[[Para [Str "4"]] - ,[Para [Str "5"]] - ,[Para [Str "6"]]]] -,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0] - [[Para [Str "X"]] - ,[Para [Str "Y"]] - ,[Para [Str "Z"]]] - [[[Para [Str "1"]] - ,[Para [Str "2"]] - ,[Para [Str "3"]]] - ,[[Para [Str "4"]] - ,[Para [Str "5"]] - ,[Para [Str "6"]]]] -,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0] - [[Para [Str "X"]] - ,[Para [Str "Y"]] - ,[Para [Str "Z"]]] - [[[Para [Str "1"]] - ,[Para [Str "2"]] - ,[Para [Str "3"]]] - ,[[Para [Str "4"]] - ,[Para [Str "5"]] - ,[Para [Str "6"]]]] -,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0] - [[Para [Str "X"]] - ,[Para [Str "Y"]] - ,[Para [Str "Z"]]] - [[[Para [Str "1"]] - ,[Para [Str "2"]] - ,[Para [Str "3"]]] - ,[[Para [Str "4"]] - ,[Para [Str "5"]] - ,[Para [Str "6"]]]] -,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0] - [[Para [Str "X"]] - ,[Para [Str "Y"]] - ,[Para [Str "Z"]]] - [[[Para [Str "1"]] - ,[Para [Str "2"]] - ,[Para [Str "3"]]] - ,[[Para [Str "4"]] - ,[Para [Str "5"]] - ,[Para [Str "6"]]]] -,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0] - [[Para [Str "X"]] - ,[Para [Str "Y"]] - ,[Para [Str "Z"]]] - [[[Para [Str "1"]] - ,[Para [Str "2"]] - ,[Para [Str "3"]]] - ,[[Para [Str "4"]] - ,[Para [Str "5"]] - ,[Para [Str "6"]]]] -,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0] - [[Para [Str "X"]] - ,[Para [Str "Y"]] - ,[Para [Str "Z"]]] - [[[Para [Str "1"]] - ,[Para [Str "2"]] - ,[Para [Str "3"]]] - ,[[Para [Str "4"]] - ,[Para [Str "5"]] - ,[Para [Str "6"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "X"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Y"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Z"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "6"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "X"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Y"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Z"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "6"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "X"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Y"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Z"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "6"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "X"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Y"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Z"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "6"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "X"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Y"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Z"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "6"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "X"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Y"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Z"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "6"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "X"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Y"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Z"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "6"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "X"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Y"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Z"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "6"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "X"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Y"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Z"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "6"]]]] + [] ,Header 2 ("tables-without-headers",[],[]) [Str "Tables",Space,Str "without",Space,Str "Headers"] -,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0] - [[] - ,[] - ,[]] - [[[Para [Str "1"]] - ,[Para [Str "2"]] - ,[Para [Str "3"]]] - ,[[Para [Str "4"]] - ,[Para [Str "5"]] - ,[Para [Str "6"]]]] -,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0] - [[] - ,[] - ,[]] - [[[Para [Str "1"]] - ,[Para [Str "2"]] - ,[Para [Str "3"]]] - ,[[Para [Str "4"]] - ,[Para [Str "5"]] - ,[Para [Str "6"]]]] -,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0] - [[] - ,[] - ,[]] - [[[Para [Str "1"]] - ,[Para [Str "2"]] - ,[Para [Str "3"]]] - ,[[Para [Str "4"]] - ,[Para [Str "5"]] - ,[Para [Str "6"]]]] -,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0] - [[] - ,[] - ,[]] - [[[Para [Str "1"]] - ,[Para [Str "2"]] - ,[Para [Str "3"]]] - ,[[Para [Str "4"]] - ,[Para [Str "5"]] - ,[Para [Str "6"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "6"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "6"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "6"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "3"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "6"]]]] + [] ,Header 2 ("empty-tables",[],[]) [Str "Empty",Space,Str "Tables"] ,Para [Str "This",Space,Str "section",Space,Str "should",Space,Str "be",Space,Str "empty."]] diff --git a/test/latex-reader.native b/test/latex-reader.native index a62f2069e..909c7dd51 100644 --- a/test/latex-reader.native +++ b/test/latex-reader.native @@ -275,18 +275,37 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,[Para [Str "$22,000",Space,Str "is",Space,Str "a",Space,Emph [Str "lot"],Space,Str "of",Space,Str "money.",Space,Str "So",Space,Str "is",Space,Str "$34,000.",Space,Str "(It",Space,Str "worked",Space,Str "if",SoftBreak,Quoted DoubleQuote [Str "lot"],Space,Str "is",Space,Str "emphasized.)"]] ,[Para [Str "Escaped",Space,Code ("",[],[]) "$",Str ":",Space,Str "$73",Space,Emph [Str "this",Space,Str "should",Space,Str "be",Space,Str "emphasized"],Space,Str "23$."]]] ,Para [Str "Here\8217s",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 "1"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignLeft,Nothing),(AlignLeft,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Animal"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Number"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Dog"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cat"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]]]] + [] ,Para [Str "A",Space,Str "table",Space,Str "with",Space,Str "one",Space,Str "column:"] -,Table [] [AlignCenter] [0.0] - [[]] - [[[Plain [Str "Animal"]]] - ,[[Plain [Str "Vegetable"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignCenter,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Animal"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Vegetable"]]]] + [] ,HorizontalRule ,Header 1 ("special-characters",[],[]) [Str "Special",Space,Str "Characters"] ,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "unicode:"] diff --git a/test/man-reader.native b/test/man-reader.native index 99c7405f8..7b2f6f966 100644 --- a/test/man-reader.native +++ b/test/man-reader.native @@ -105,76 +105,170 @@ Pandoc (Meta {unMeta = fromList [("date",MetaInlines [Str "Oct",Space,Str "17,", ,Header 1 ("",[],[]) [Str "Macros"] ,Para [Strong [Str "Me",Space,Str "Myself"],Space,Str "and",Space,Str "I.",Space,Emph [Str "The",Space,Str "author",Space,Str "is",Space,Str "John",Space,Str "Jones."],Space,Str "It's",Space,Str "The",Space,Strong [Str "Author"],Str "."] ,Header 1 ("",[],[]) [Str "Tables"] -,Table [] [AlignRight,AlignLeft,AlignCenter,AlignLeft] [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 "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]]] - ,[[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]]] - ,[[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]]]] -,Table [] [AlignRight,AlignLeft,AlignCenter,AlignLeft] [0.0,0.0,0.0,0.0] - [[Plain [Str "Right"]] - ,[Plain [Str "Left"]] - ,[Plain [Str "Center"]] - ,[Plain [Str "Left",Space,Emph [Str "more"]]]] - [[[Plain [Str "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]]] - ,[[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]]] - ,[[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]]]] -,Table [] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.0,0.0,0.0,0.0] - [[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 "row"]] - ,[Plain [Str "12.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."]]] - ,[[Plain [Str "Second"]] - ,[Plain [Str "row"]] - ,[Plain [Str "5.0"]] - ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignLeft,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Right"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Center"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignLeft,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Right"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Center"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left",Space,Emph [Str "more"]]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignCenter,Nothing),(AlignLeft,Nothing),(AlignRight,Nothing),(AlignLeft,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Centered",Space,Str "Header"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left",Space,Str "Aligned"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Right",Space,Str "Aligned"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default",Space,Str "aligned"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "First"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "row"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12.0"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines."]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Second"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "row"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5.0"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]] + [] ,Para [Str "Table",Space,Str "without",Space,Str "column",Space,Str "headers:"] -,Table [] [AlignRight,AlignLeft,AlignCenter,AlignRight] [0.0,0.0,0.0,0.0] - [[] - ,[] - ,[] - ,[]] - [[[Plain [Str "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]]] - ,[[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]]] - ,[[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]]]] -,Table [] [AlignRight,AlignLeft] [0.5,0.5] - [[] - ,[]] - [[[Plain [Str "a"]] - ,[Plain [Str "b"]]] - ,[[Para [Str "one"] +,Table ("",[],[]) (Caption Nothing + []) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignRight,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignRight,Just 0.5),(AlignLeft,Just 0.5)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "a"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "b"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "one"] ,Para [Str "two"]] - ,[CodeBlock ("",[],[]) "some\n code"]]]] + ,Cell ("",[],[]) Nothing 1 1 + [CodeBlock ("",[],[]) "some\n code"]]] + []] diff --git a/test/markdown-reader-more.native b/test/markdown-reader-more.native index 9c128ab94..21bd052ac 100644 --- a/test/markdown-reader-more.native +++ b/test/markdown-reader-more.native @@ -96,84 +96,176 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "Author",S ,[Str "Continuation",Space,Str "line"] ,[Str "\160\160and",Space,Str "another"]] ,Header 2 ("grid-tables",[],[]) [Str "Grid",Space,Str "Tables"] -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.2638888888888889,0.16666666666666666,0.18055555555555555] - [[Plain [Str "col",Space,Str "1"]] - ,[Plain [Str "col",Space,Str "2"]] - ,[Plain [Str "col",Space,Str "3"]]] - [[[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]] - ,[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]] - ,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]] - ,[[Plain [Str "r2",Space,Str "d"]] - ,[Plain [Str "e"]] - ,[Plain [Str "f"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Just 0.2638888888888889),(AlignDefault,Just 0.16666666666666666),(AlignDefault,Just 0.18055555555555555)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "col",Space,Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "col",Space,Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "col",Space,Str "3"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "r2",Space,Str "d"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "e"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "f"]]]] + [] ,Para [Str "Headless"] -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.2638888888888889,0.16666666666666666,0.18055555555555555] - [[] - ,[] - ,[]] - [[[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]] - ,[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]] - ,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]] - ,[[Plain [Str "r2",Space,Str "d"]] - ,[Plain [Str "e"]] - ,[Plain [Str "f"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Just 0.2638888888888889),(AlignDefault,Just 0.16666666666666666),(AlignDefault,Just 0.18055555555555555)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "r2",Space,Str "d"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "e"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "f"]]]] + [] ,Para [Str "With",Space,Str "alignments"] -,Table [] [AlignRight,AlignLeft,AlignCenter] [0.2638888888888889,0.16666666666666666,0.18055555555555555] - [[Plain [Str "col",Space,Str "1"]] - ,[Plain [Str "col",Space,Str "2"]] - ,[Plain [Str "col",Space,Str "3"]]] - [[[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]] - ,[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]] - ,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]] - ,[[Plain [Str "r2",Space,Str "d"]] - ,[Plain [Str "e"]] - ,[Plain [Str "f"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignRight,Just 0.2638888888888889),(AlignLeft,Just 0.16666666666666666),(AlignCenter,Just 0.18055555555555555)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "col",Space,Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "col",Space,Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "col",Space,Str "3"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "r2",Space,Str "d"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "e"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "f"]]]] + [] ,Para [Str "Headless",Space,Str "with",Space,Str "alignments"] -,Table [] [AlignRight,AlignLeft,AlignCenter] [0.2638888888888889,0.16666666666666666,0.18055555555555555] - [[] - ,[] - ,[]] - [[[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]] - ,[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]] - ,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]] - ,[[Plain [Str "r2",Space,Str "d"]] - ,[Plain [Str "e"]] - ,[Plain [Str "f"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignRight,Just 0.2638888888888889),(AlignLeft,Just 0.16666666666666666),(AlignCenter,Just 0.18055555555555555)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "r2",Space,Str "d"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "e"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "f"]]]] + [] ,Para [Str "Spaces",Space,Str "at",Space,Str "ends",Space,Str "of",Space,Str "lines"] -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.2638888888888889,0.16666666666666666,0.18055555555555555] - [[] - ,[] - ,[]] - [[[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]] - ,[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]] - ,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]] - ,[[Plain [Str "r2",Space,Str "d"]] - ,[Plain [Str "e"]] - ,[Plain [Str "f"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Just 0.2638888888888889),(AlignDefault,Just 0.16666666666666666),(AlignDefault,Just 0.18055555555555555)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "r2",Space,Str "d"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "e"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "f"]]]] + [] ,Para [Str "Multiple",Space,Str "blocks",Space,Str "in",Space,Str "a",Space,Str "cell"] -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.2638888888888889,0.16666666666666666,0.18055555555555555] - [[] - ,[] - ,[]] - [[[Header 1 ("col-1",[],[]) [Str "col",Space,Str "1"] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Just 0.2638888888888889),(AlignDefault,Just 0.16666666666666666),(AlignDefault,Just 0.18055555555555555)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Header 1 ("col-1",[],[]) [Str "col",Space,Str "1"] ,Plain [Str "col",Space,Str "1"]] - ,[Header 1 ("col-2",[],[]) [Str "col",Space,Str "2"] + ,Cell ("",[],[]) Nothing 1 1 + [Header 1 ("col-2",[],[]) [Str "col",Space,Str "2"] ,Plain [Str "col",Space,Str "2"]] - ,[Header 1 ("col-3",[],[]) [Str "col",Space,Str "3"] + ,Cell ("",[],[]) Nothing 1 1 + [Header 1 ("col-3",[],[]) [Str "col",Space,Str "3"] ,Plain [Str "col",Space,Str "3"]]] - ,[[Para [Str "r1",Space,Str "a"] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "r1",Space,Str "a"] ,Para [Str "r1",Space,Str "bis"]] - ,[BulletList + ,Cell ("",[],[]) Nothing 1 1 + [BulletList [[Plain [Str "b"]] ,[Plain [Str "b",Space,Str "2"]] ,[Plain [Str "b",Space,Str "2"]]]] - ,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2",SoftBreak,Str "c",Space,Str "2"]]]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "c",SoftBreak,Str "c",Space,Str "2",SoftBreak,Str "c",Space,Str "2"]]]] + [] ,Para [Str "Empty",Space,Str "cells"] -,Table [] [AlignDefault,AlignDefault] [5.555555555555555e-2,5.555555555555555e-2] - [[] - ,[]] - [[[] - ,[]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Just 5.555555555555555e-2),(AlignDefault,Just 5.555555555555555e-2)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [] ,Header 2 ("entities-in-links-and-titles",[],[]) [Str "Entities",Space,Str "in",Space,Str "links",Space,Str "and",Space,Str "titles"] ,Para [Link ("",[],[]) [Str "link"] ("/\252rl","\246\246!")] ,Para [Link ("",["uri"],[]) [Str "http://g\246\246gle.com"] ("http://g\246\246gle.com","")] diff --git a/test/mediawiki-reader.native b/test/mediawiki-reader.native index 965930478..0300419c5 100644 --- a/test/mediawiki-reader.native +++ b/test/mediawiki-reader.native @@ -187,76 +187,177 @@ Pandoc (Meta {unMeta = fromList []}) ,RawBlock (Format "mediawiki") "{{Thankyou|all your effort|Me}}" ,Para [Str "Written",Space,RawInline (Format "mediawiki") "{{{date}}}",Space,Str "by",Space,RawInline (Format "mediawiki") "{{{name}}}",Str "."] ,Header 2 ("tables",[],[]) [Str "tables"] -,Table [] [AlignDefault,AlignDefault] [0.0,0.0] - [[] - ,[]] - [[[Para [Str "Orange"]] - ,[Para [Str "Apple"]]] - ,[[Para [Str "Bread"]] - ,[Para [Str "Pie"]]] - ,[[Para [Str "Butter"]] - ,[Para [Str "Ice",Space,Str "cream"]]]] -,Table [Str "Food",Space,Str "complements"] [AlignDefault,AlignDefault] [0.0,0.0] - [[Para [Str "Orange"]] - ,[Para [Str "Apple"]]] - [[[Para [Str "Bread"]] - ,[Para [Str "Pie"]]] - ,[[Para [Str "Butter"]] - ,[Para [Str "Ice",Space,Str "cream"]]]] -,Table [Str "Food",Space,Str "complements"] [AlignDefault,AlignDefault] [0.0,0.0] - [[Para [Str "Orange"]] - ,[Para [Str "Apple"]]] - [[[Para [Str "Bread"] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "Orange"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Apple"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "Bread"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Pie"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "Butter"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Ice",Space,Str "cream"]]]] + [] +,Table ("",[],[]) (Caption Nothing + [Para [Str "Food",Space,Str "complements"]]) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "Orange"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Apple"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "Bread"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Pie"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "Butter"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Ice",Space,Str "cream"]]]] + [] +,Table ("",[],[]) (Caption Nothing + [Para [Str "Food",Space,Str "complements"]]) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "Orange"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Apple"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "Bread"] ,Para [Str "and",Space,Str "cheese"]] - ,[Para [Str "Pie"] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Pie"] ,OrderedList (1,DefaultStyle,DefaultDelim) [[Plain [Str "apple"]] ,[Plain [Str "carrot"]]]]]] -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[] - ,[] - ,[]] - [[[Para [Str "Orange"]] - ,[Para [Str "Apple"]] - ,[Para [Str "more"]]] - ,[[Para [Str "Bread"]] - ,[Para [Str "Pie"]] - ,[Para [Str "more"]]] - ,[[Para [Str "Butter"]] - ,[Para [Str "Ice",Space,Str "cream"]] - ,[Para [Str "and",Space,Str "more"]]]] -,Table [] [AlignLeft,AlignRight,AlignCenter] [0.25,0.125,0.125] - [[Para [Str "Left"]] - ,[Para [Str "Right"]] - ,[Para [Str "Center"]]] - [[[Para [Str "left"]] - ,[Para [Str "15.00"]] - ,[Para [Str "centered"]]] - ,[[Para [Str "more"]] - ,[Para [Str "2.0"]] - ,[Para [Str "more"]]]] -,Table [] [AlignDefault,AlignDefault] [0.0,0.0] - [[] - ,[]] - [[[Para [Str "Orange"]] - ,[Para [Str "Apple"]]] - ,[[Para [Str "Bread"]] - ,[Table [] [AlignDefault,AlignDefault] [0.0,0.0] - [[Para [Str "fruit"]] - ,[Para [Str "topping"]]] - [[[Para [Str "apple"]] - ,[Para [Str "ice",Space,Str "cream"]]]]]] - ,[[Para [Str "Butter"]] - ,[Para [Str "Ice",Space,Str "cream"]]]] -,Table [] [AlignDefault] [0.0] - [[]] - [[[Para [Str "Orange"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "Orange"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Apple"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "more"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "Bread"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Pie"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "more"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "Butter"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Ice",Space,Str "cream"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "and",Space,Str "more"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignLeft,Just 0.25),(AlignRight,Just 0.125),(AlignCenter,Just 0.125)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "Left"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Right"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Center"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "left"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "15.00"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "centered"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "more"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "2.0"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "more"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "Orange"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Apple"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "Bread"]] + ,Cell ("",[],[]) Nothing 1 1 + [Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "fruit"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "topping"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "apple"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "ice",Space,Str "cream"]]]] + []]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "Butter"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "Ice",Space,Str "cream"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "Orange"]]]] + [] ,Para [Str "Paragraph",Space,Str "after",Space,Str "the",Space,Str "table."] -,Table [] [AlignDefault,AlignDefault] [0.0,0.0] - [[Para [Str "fruit"]] - ,[Para [Str "topping"]]] - [[[Para [Str "apple"]] - ,[Para [Str "ice",Space,Str "cream"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "fruit"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "topping"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "apple"]] + ,Cell ("",[],[]) Nothing 1 1 + [Para [Str "ice",Space,Str "cream"]]]] + [] ,Header 2 ("notes",[],[]) [Str "notes"] ,Para [Str "My",Space,Str "note!",Note [Plain [Str "This."]]] ,Para [Str "URL",Space,Str "note.",Note [Plain [Link ("",[],[]) [Str "http://docs.python.org/library/functions.html#range"] ("http://docs.python.org/library/functions.html#range","")]]]] diff --git a/test/odt/native/simpleTable.native b/test/odt/native/simpleTable.native index 0a9b380a5..0fd7a918d 100644 --- a/test/odt/native/simpleTable.native +++ b/test/odt/native/simpleTable.native @@ -1 +1 @@ -[Table [] [AlignDefault,AlignDefault] [0.0,0.0] [[],[]] [[[Plain [Str "Content"]],[Plain [Str "More",Space,Str "content"]]]],Para []] +[Table ("",[],[]) (Caption Nothing []) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 [Row ("",[],[]) [Cell ("",[],[]) Nothing 1 1 [],Cell ("",[],[]) Nothing 1 1 []]] [Row ("",[],[]) [Cell ("",[],[]) Nothing 1 1 [Plain [Str "Content"]],Cell ("",[],[]) Nothing 1 1 [Plain [Str "More",Space,Str "content"]]]] [],Para []] diff --git a/test/odt/native/simpleTableWithCaption.native b/test/odt/native/simpleTableWithCaption.native index 18d68b772..8e2b49417 100644 --- a/test/odt/native/simpleTableWithCaption.native +++ b/test/odt/native/simpleTableWithCaption.native @@ -1 +1 @@ -[Table [Str "Table",Space,Str "1:",Space,Str "Some",Space,Str "caption",Space,Str "for",Space,Str "a",Space,Str "table"] [AlignDefault,AlignDefault] [0.0,0.0] [[],[]] [[[Plain [Str "Content"]],[Plain [Str "More",Space,Str "content"]]]],Para []] +[Table ("",[],[]) (Caption Nothing [Para [Str "Table",Space,Str "1:",Space,Str "Some",Space,Str "caption",Space,Str "for",Space,Str "a",Space,Str "table"]]) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 [Row ("",[],[]) [Cell ("",[],[]) Nothing 1 1 [],Cell ("",[],[]) Nothing 1 1 []]] [Row ("",[],[]) [Cell ("",[],[]) Nothing 1 1 [Plain [Str "Content"]],Cell ("",[],[]) Nothing 1 1 [Plain [Str "More",Space,Str "content"]]]] [],Para []] diff --git a/test/odt/native/tableWithContents.native b/test/odt/native/tableWithContents.native index b1d3c5765..b71888516 100644 --- a/test/odt/native/tableWithContents.native +++ b/test/odt/native/tableWithContents.native @@ -1 +1 @@ -[Table [] [AlignDefault,AlignDefault] [0.0,0.0] [[],[]] [[[Plain [Str "A"]],[Plain [Str "B"]]],[[Plain [Str "C"]],[Plain [Str "D"]]]],Para []] +[Table ("",[],[]) (Caption Nothing []) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 [Row ("",[],[]) [Cell ("",[],[]) Nothing 1 1 [],Cell ("",[],[]) Nothing 1 1 []]] [Row ("",[],[]) [Cell ("",[],[]) Nothing 1 1 [Plain [Str "A"]],Cell ("",[],[]) Nothing 1 1 [Plain [Str "B"]]],Row ("",[],[]) [Cell ("",[],[]) Nothing 1 1 [Plain [Str "C"]],Cell ("",[],[]) Nothing 1 1 [Plain [Str "D"]]]] [],Para []] diff --git a/test/pipe-tables.native b/test/pipe-tables.native index ca9858d1f..f4757756b 100644 --- a/test/pipe-tables.native +++ b/test/pipe-tables.native @@ -1,115 +1,264 @@ [Para [Str "Simplest",Space,Str "table",Space,Str "without",Space,Str "caption:"] -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[Plain [Str "Default1"]] - ,[Plain [Str "Default2"]] - ,[Plain [Str "Default3"]]] - [[[Plain [Str "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]]] - ,[[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]]] - ,[[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default3"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]]]] + [] ,Para [Str "Simple",Space,Str "table",Space,Str "with",Space,Str "caption:"] -,Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."] [AlignRight,AlignLeft,AlignDefault,AlignCenter] [0.0,0.0,0.0,0.0] - [[Plain [Str "Right"]] - ,[Plain [Str "Left"]] - ,[Plain [Str "Default"]] - ,[Plain [Str "Center"]]] - [[[Plain [Str "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]]] - ,[[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]]] - ,[[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]]]] +,Table ("",[],[]) (Caption Nothing + [Para [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."]]) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignDefault,Nothing),(AlignCenter,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Right"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Center"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]]]] + [] ,Para [Str "Simple",Space,Str "table",Space,Str "without",Space,Str "caption:"] -,Table [] [AlignRight,AlignLeft,AlignCenter] [0.0,0.0,0.0] - [[Plain [Str "Right"]] - ,[Plain [Str "Left"]] - ,[Plain [Str "Center"]]] - [[[Plain [Str "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]]] - ,[[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]]] - ,[[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Right"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Center"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]]]] + [] ,Para [Str "Headerless",Space,Str "table",Space,Str "without",Space,Str "caption:"] -,Table [] [AlignRight,AlignLeft,AlignCenter] [0.0,0.0,0.0] - [[] - ,[] - ,[]] - [[[Plain [Str "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]]] - ,[[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]]] - ,[[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]]]] + [] ,Para [Str "Table",Space,Str "without",Space,Str "sides:"] -,Table [] [AlignDefault,AlignRight] [0.0,0.0] - [[Plain [Str "Fruit"]] - ,[Plain [Str "Quantity"]]] - [[[Plain [Str "apple"]] - ,[Plain [Str "5"]]] - ,[[Plain [Str "orange"]] - ,[Plain [Str "17"]]] - ,[[Plain [Str "pear"]] - ,[Plain [Str "302"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignRight,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Fruit"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Quantity"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "apple"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "orange"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "17"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "pear"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "302"]]]] + [] ,Para [Str "One-column:"] -,Table [] [AlignDefault] [0.0] - [[Plain [Str "hi"]]] - [[[Plain [Str "lo"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "hi"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "lo"]]]] + [] ,Para [Str "Header-less",Space,Str "one-column:"] -,Table [] [AlignCenter] [0.0] - [[]] - [[[Plain [Str "hi"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignCenter,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "hi"]]]] + [] ,Para [Str "Indented",Space,Str "left",Space,Str "column:"] -,Table [] [AlignRight,AlignLeft] [0.0,0.0] - [[Plain [Str "Number",Space,Str "of",Space,Str "siblings"]] - ,[Plain [Str "Salary"]]] - [[[Plain [Str "3"]] - ,[Plain [Str "33"]]] - ,[[Plain [Str "4"]] - ,[Plain [Str "44"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignRight,Nothing),(AlignLeft,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Number",Space,Str "of",Space,Str "siblings"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Salary"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "33"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "44"]]]] + [] ,Para [Str "Long",Space,Str "pipe",Space,Str "table",Space,Str "with",Space,Str "relative",Space,Str "widths:"] -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.15517241379310345,0.1724137931034483,0.6724137931034483] - [[Plain [Str "Default1"]] - ,[Plain [Str "Default2"]] - ,[Plain [Str "Default3"]]] - [[[Plain [Str "123"]] - ,[Plain [Str "this",Space,Str "is",Space,Str "a",Space,Str "table",Space,Str "cell"]] - ,[Plain [Str "and",Space,Str "this",Space,Str "is",Space,Str "a",Space,Str "really",Space,Str "long",Space,Str "table",Space,Str "cell",Space,Str "that",Space,Str "will",Space,Str "probably",Space,Str "need",Space,Str "wrapping"]]] - ,[[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Just 0.15517241379310345),(AlignDefault,Just 0.1724137931034483),(AlignDefault,Just 0.6724137931034483)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default3"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "this",Space,Str "is",Space,Str "a",Space,Str "table",Space,Str "cell"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "and",Space,Str "this",Space,Str "is",Space,Str "a",Space,Str "really",Space,Str "long",Space,Str "table",Space,Str "cell",Space,Str "that",Space,Str "will",Space,Str "probably",Space,Str "need",Space,Str "wrapping"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]]]] + [] ,Para [Str "Pipe",Space,Str "table",Space,Str "with",Space,Str "no",Space,Str "body:"] -,Table [] [AlignDefault] [0.0] - [[Plain [Str "Header"]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Header"]]]] + [] [] ,Para [Str "Pipe",Space,Str "table",Space,Str "with",Space,Str "tricky",Space,Str "cell",Space,Str "contents",Space,Str "(see",Space,Str "#2765):"] -,Table [] [AlignLeft,AlignRight,AlignRight] [0.0,0.0,0.0] - [[] - ,[Plain [Str "IP_gene8-_1st"]] - ,[Plain [Str "IP_gene8+_1st"]]] - [[[Plain [Str "IP_gene8-_1st"]] - ,[Plain [Str "1.0000000"]] - ,[Plain [Str "0.4357325"]]] - ,[[Plain [Str "IP_gene8+_1st"]] - ,[Plain [Str "0.4357325"]] - ,[Plain [Str "1.0000000"]]] - ,[[Plain [Str "foo",Code ("",[],[]) "bar|baz"]] - ,[Plain [Str "and|escaped"]] - ,[Plain [Str "3.0000000"]]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignLeft,Nothing),(AlignRight,Nothing),(AlignRight,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "IP_gene8-_1st"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "IP_gene8+_1st"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "IP_gene8-_1st"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1.0000000"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "0.4357325"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "IP_gene8+_1st"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "0.4357325"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1.0000000"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "foo",Code ("",[],[]) "bar|baz"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "and|escaped"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3.0000000"]]]] + []] diff --git a/test/pptx/speaker_notes_afterseps.native b/test/pptx/speaker_notes_afterseps.native index 30910708c..1e4ac331c 100644 --- a/test/pptx/speaker_notes_afterseps.native +++ b/test/pptx/speaker_notes_afterseps.native @@ -1,23 +1,45 @@ [Para [Image ("",[],[]) [Str "The",Space,Str "moon"] ("lalune.jpg","fig:")] ,Div ("",["notes"],[]) [Para [Str "chicken",Space,Str "and",Space,Str "dumplings"]] -,Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax,",Space,Str "with",Space,Str "alignment"] [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 "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]]] - ,[[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]]] - ,[[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]]]] +,Table ("",[],[]) (Caption Nothing + [Para [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax,",Space,Str "with",Space,Str "alignment"]]) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Right"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Center"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]]]] + [] ,Div ("",["notes"],[]) [Para [Str "foo",Space,Str "bar"]] ,Div ("",["columns"],[]) diff --git a/test/pptx/tables.native b/test/pptx/tables.native index e41b7bc8d..1541e6d93 100644 --- a/test/pptx/tables.native +++ b/test/pptx/tables.native @@ -1,35 +1,79 @@ [Header 2 ("a-table-with-a-caption",[],[]) [Str "A",Space,Str "Table,",Space,Str "with",Space,Str "a",Space,Str "caption"] -,Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax,",Space,Str "with",Space,Str "alignment"] [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 "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]]] - ,[[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]]] - ,[[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]]]] -,Table [] [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 "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]]] - ,[[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]]] - ,[[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]]]]] +,Table ("",[],[]) (Caption Nothing + [Para [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax,",Space,Str "with",Space,Str "alignment"]]) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Right"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Center"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Right"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Center"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]]]] + []] diff --git a/test/rst-reader.native b/test/rst-reader.native index d4322f9ae..485d566ca 100644 --- a/test/rst-reader.native +++ b/test/rst-reader.native @@ -244,72 +244,152 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,[Str "Continuation",Space,Str "line"] ,[Str "\160\160and",Space,Str "another"]] ,Header 1 ("simple-tables",[],[]) [Str "Simple",Space,Str "Tables"] -,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 "b"]] - ,[Plain [Str "c"]]] - ,[[Plain [Str "r2",Space,Str "d"]] - ,[Plain [Str "e"]] - ,[Plain [Str "f"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "col",Space,Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "col",Space,Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "col",Space,Str "3"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "r1",Space,Str "a"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "b"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "c"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "r2",Space,Str "d"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "e"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "f"]]]] + [] ,Para [Str "Headless"] -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[] - ,[] - ,[]] - [[[Plain [Str "r1",Space,Str "a"]] - ,[Plain [Str "b"]] - ,[Plain [Str "c"]]] - ,[[Plain [Str "r2",Space,Str "d"]] - ,[Plain [Str "e"]] - ,[Plain [Str "f"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "r1",Space,Str "a"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "b"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "c"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "r2",Space,Str "d"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "e"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "f"]]]] + [] ,Header 1 ("grid-tables",[],[]) [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",SoftBreak,Str "r1",Space,Str "bis"]] - ,[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]] - ,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]] - ,[[Plain [Str "r2",Space,Str "d"]] - ,[Plain [Str "e"]] - ,[Plain [Str "f"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Just 0.2375),(AlignDefault,Just 0.15),(AlignDefault,Just 0.1625)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "col",Space,Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "col",Space,Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "col",Space,Str "3"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "r2",Space,Str "d"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "e"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "f"]]]] + [] ,Para [Str "Headless"] -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.2375,0.15,0.1625] - [[] - ,[] - ,[]] - [[[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]] - ,[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]] - ,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]] - ,[[Plain [Str "r2",Space,Str "d"]] - ,[Plain [Str "e"]] - ,[Plain [Str "f"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Just 0.2375),(AlignDefault,Just 0.15),(AlignDefault,Just 0.1625)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "r2",Space,Str "d"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "e"]] + ,Cell ("",[],[]) Nothing 1 1 + [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",SoftBreak,Str "r1",Space,Str "bis"]] - ,[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]] - ,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]] - ,[[Plain [Str "r2",Space,Str "d"]] - ,[Plain [Str "e"]] - ,[Plain [Str "f"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Just 0.2375),(AlignDefault,Just 0.15),(AlignDefault,Just 0.1625)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "r2",Space,Str "d"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "e"]] + ,Cell ("",[],[]) Nothing 1 1 + [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"] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Just 0.2375),(AlignDefault,Just 0.15),(AlignDefault,Just 0.1625)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Para [Str "r1",Space,Str "a"] ,Para [Str "r1",Space,Str "bis"]] - ,[BulletList + ,Cell ("",[],[]) Nothing 1 1 + [BulletList [[Plain [Str "b"]] ,[Plain [Str "b",Space,Str "2"]] ,[Plain [Str "b",Space,Str "2"]]]] - ,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2",SoftBreak,Str "c",Space,Str "2"]]]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "c",SoftBreak,Str "c",Space,Str "2",SoftBreak,Str "c",Space,Str "2"]]]] + [] ,Header 1 ("footnotes",[],[]) [Str "Footnotes"] ,Para [Note [Para [Str "Note",Space,Str "with",Space,Str "one",Space,Str "line."]]] ,Para [Note [Para [Str "Note",Space,Str "with",SoftBreak,Str "continuation",Space,Str "line."]]] diff --git a/test/tables-rstsubset.native b/test/tables-rstsubset.native index a4f801b1c..bb2a99997 100644 --- a/test/tables-rstsubset.native +++ b/test/tables-rstsubset.native @@ -1,114 +1,253 @@ [Para [Str "Simple",Space,Str "table",Space,Str "with",Space,Str "caption:"] -,Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."] [AlignDefault,AlignDefault,AlignDefault,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 "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]]] - ,[[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]]] - ,[[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]]]] +,Table ("",[],[]) (Caption Nothing + [Para [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."]]) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Right"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Center"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]]]] + [] ,Para [Str "Simple",Space,Str "table",Space,Str "without",Space,Str "caption:"] -,Table [] [AlignDefault,AlignDefault,AlignDefault,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 "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]]] - ,[[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]]] - ,[[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Right"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Center"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]]]] + [] ,Para [Str "Simple",Space,Str "table",Space,Str "indented",Space,Str "two",Space,Str "spaces:"] -,Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."] [AlignDefault,AlignDefault,AlignDefault,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 "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]]] - ,[[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]]] - ,[[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]]]] +,Table ("",[],[]) (Caption Nothing + [Para [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."]]) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Right"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Center"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]]]] + [] ,Para [Str "Multiline",Space,Str "table",Space,Str "with",Space,Str "caption:"] -,Table [Str "Here\8217s",Space,Str "the",Space,Str "caption.",Space,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.1375,0.125,0.15,0.3375] - [[Plain [Str "Centered",SoftBreak,Str "Header"]] - ,[Plain [Str "Left",SoftBreak,Str "Aligned"]] - ,[Plain [Str "Right",SoftBreak,Str "Aligned"]] - ,[Plain [Str "Default",Space,Str "aligned"]]] - [[[Plain [Str "First"]] - ,[Plain [Str "row"]] - ,[Plain [Str "12.0"]] - ,[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",SoftBreak,Str "spans",Space,Str "multiple",Space,Str "lines."]]] - ,[[Plain [Str "Second"]] - ,[Plain [Str "row"]] - ,[Plain [Str "5.0"]] - ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]] +,Table ("",[],[]) (Caption Nothing + [Para [Str "Here\8217s",Space,Str "the",Space,Str "caption.",Space,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."]]) [(AlignDefault,Just 0.1375),(AlignDefault,Just 0.125),(AlignDefault,Just 0.15),(AlignDefault,Just 0.3375)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Centered",SoftBreak,Str "Header"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left",SoftBreak,Str "Aligned"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Right",SoftBreak,Str "Aligned"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default",Space,Str "aligned"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "First"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "row"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12.0"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",SoftBreak,Str "spans",Space,Str "multiple",Space,Str "lines."]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Second"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "row"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5.0"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]] + [] ,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "caption:"] -,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.1375,0.125,0.15,0.3375] - [[Plain [Str "Centered",SoftBreak,Str "Header"]] - ,[Plain [Str "Left",SoftBreak,Str "Aligned"]] - ,[Plain [Str "Right",SoftBreak,Str "Aligned"]] - ,[Plain [Str "Default",Space,Str "aligned"]]] - [[[Plain [Str "First"]] - ,[Plain [Str "row"]] - ,[Plain [Str "12.0"]] - ,[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",SoftBreak,Str "spans",Space,Str "multiple",Space,Str "lines."]]] - ,[[Plain [Str "Second"]] - ,[Plain [Str "row"]] - ,[Plain [Str "5.0"]] - ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Just 0.1375),(AlignDefault,Just 0.125),(AlignDefault,Just 0.15),(AlignDefault,Just 0.3375)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Centered",SoftBreak,Str "Header"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left",SoftBreak,Str "Aligned"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Right",SoftBreak,Str "Aligned"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default",Space,Str "aligned"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "First"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "row"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12.0"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",SoftBreak,Str "spans",Space,Str "multiple",Space,Str "lines."]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Second"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "row"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5.0"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]] + [] ,Para [Str "Table",Space,Str "without",Space,Str "column",Space,Str "headers:"] -,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0,0.0] - [[] - ,[] - ,[] - ,[]] - [[[Plain [Str "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]]] - ,[[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]]] - ,[[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]]]] + [] ,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "column",Space,Str "headers:"] -,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.1375,0.125,0.15,0.3375] - [[] - ,[] - ,[] - ,[]] - [[[Plain [Str "First"]] - ,[Plain [Str "row"]] - ,[Plain [Str "12.0"]] - ,[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",SoftBreak,Str "spans",Space,Str "multiple",Space,Str "lines."]]] - ,[[Plain [Str "Second"]] - ,[Plain [Str "row"]] - ,[Plain [Str "5.0"]] - ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Just 0.1375),(AlignDefault,Just 0.125),(AlignDefault,Just 0.15),(AlignDefault,Just 0.3375)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "First"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "row"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12.0"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",SoftBreak,Str "spans",Space,Str "multiple",Space,Str "lines."]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Second"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "row"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5.0"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]] + []] diff --git a/test/tables.native b/test/tables.native index 62ed56bb4..da3df8b47 100644 --- a/test/tables.native +++ b/test/tables.native @@ -1,114 +1,253 @@ [Para [Str "Simple",Space,Str "table",Space,Str "with",Space,Str "caption:"] -,Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."] [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 "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]]] - ,[[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]]] - ,[[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]]]] +,Table ("",[],[]) (Caption Nothing + [Para [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."]]) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Right"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Center"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]]]] + [] ,Para [Str "Simple",Space,Str "table",Space,Str "without",Space,Str "caption:"] -,Table [] [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 "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]]] - ,[[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]]] - ,[[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Right"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Center"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]]]] + [] ,Para [Str "Simple",Space,Str "table",Space,Str "indented",Space,Str "two",Space,Str "spaces:"] -,Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."] [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 "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]]] - ,[[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]]] - ,[[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]]]] +,Table ("",[],[]) (Caption Nothing + [Para [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."]]) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Right"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Center"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]]]] + [] ,Para [Str "Multiline",Space,Str "table",Space,Str "with",Space,Str "caption:"] -,Table [Str "Here\8217s",Space,Str "the",Space,Str "caption.",SoftBreak,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.15,0.1375,0.1625,0.35] - [[Plain [Str "Centered",SoftBreak,Str "Header"]] - ,[Plain [Str "Left",SoftBreak,Str "Aligned"]] - ,[Plain [Str "Right",SoftBreak,Str "Aligned"]] - ,[Plain [Str "Default",Space,Str "aligned"]]] - [[[Plain [Str "First"]] - ,[Plain [Str "row"]] - ,[Plain [Str "12.0"]] - ,[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",SoftBreak,Str "multiple",Space,Str "lines."]]] - ,[[Plain [Str "Second"]] - ,[Plain [Str "row"]] - ,[Plain [Str "5.0"]] - ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]] +,Table ("",[],[]) (Caption Nothing + [Para [Str "Here\8217s",Space,Str "the",Space,Str "caption.",SoftBreak,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."]]) [(AlignCenter,Just 0.15),(AlignLeft,Just 0.1375),(AlignRight,Just 0.1625),(AlignLeft,Just 0.35)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Centered",SoftBreak,Str "Header"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left",SoftBreak,Str "Aligned"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Right",SoftBreak,Str "Aligned"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default",Space,Str "aligned"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "First"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "row"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12.0"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",SoftBreak,Str "multiple",Space,Str "lines."]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Second"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "row"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5.0"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]] + [] ,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "caption:"] -,Table [] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.15,0.1375,0.1625,0.35] - [[Plain [Str "Centered",SoftBreak,Str "Header"]] - ,[Plain [Str "Left",SoftBreak,Str "Aligned"]] - ,[Plain [Str "Right",SoftBreak,Str "Aligned"]] - ,[Plain [Str "Default",Space,Str "aligned"]]] - [[[Plain [Str "First"]] - ,[Plain [Str "row"]] - ,[Plain [Str "12.0"]] - ,[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",SoftBreak,Str "multiple",Space,Str "lines."]]] - ,[[Plain [Str "Second"]] - ,[Plain [Str "row"]] - ,[Plain [Str "5.0"]] - ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignCenter,Just 0.15),(AlignLeft,Just 0.1375),(AlignRight,Just 0.1625),(AlignLeft,Just 0.35)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Centered",SoftBreak,Str "Header"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Left",SoftBreak,Str "Aligned"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Right",SoftBreak,Str "Aligned"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Default",Space,Str "aligned"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "First"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "row"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12.0"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",SoftBreak,Str "multiple",Space,Str "lines."]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Second"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "row"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5.0"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]] + [] ,Para [Str "Table",Space,Str "without",Space,Str "column",Space,Str "headers:"] -,Table [] [AlignRight,AlignLeft,AlignCenter,AlignRight] [0.0,0.0,0.0,0.0] - [[] - ,[] - ,[] - ,[]] - [[[Plain [Str "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]] - ,[Plain [Str "12"]]] - ,[[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]] - ,[Plain [Str "123"]]] - ,[[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]] - ,[Plain [Str "1"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignRight,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]]]] + [] ,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "column",Space,Str "headers:"] -,Table [] [AlignCenter,AlignLeft,AlignRight,AlignDefault] [0.15,0.1375,0.1625,0.35] - [[] - ,[] - ,[] - ,[]] - [[[Plain [Str "First"]] - ,[Plain [Str "row"]] - ,[Plain [Str "12.0"]] - ,[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",SoftBreak,Str "multiple",Space,Str "lines."]]] - ,[[Plain [Str "Second"]] - ,[Plain [Str "row"]] - ,[Plain [Str "5.0"]] - ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignCenter,Just 0.15),(AlignLeft,Just 0.1375),(AlignRight,Just 0.1625),(AlignDefault,Just 0.35)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "First"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "row"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "12.0"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",SoftBreak,Str "multiple",Space,Str "lines."]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Second"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "row"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5.0"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]] + []] diff --git a/test/textile-reader.native b/test/textile-reader.native index 16b5a87e8..2f2f58818 100644 --- a/test/textile-reader.native +++ b/test/textile-reader.native @@ -103,37 +103,77 @@ Pandoc (Meta {unMeta = fromList []}) ,Header 1 ("tables",[],[]) [Str "Tables"] ,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 ("without-headers",[],[]) [Str "Without",Space,Str "headers"] -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[] - ,[] - ,[]] - [[[Plain [Str "name"]] - ,[Plain [Str "age"]] - ,[Plain [Str "sex"]]] - ,[[Plain [Str "joan"]] - ,[Plain [Str "24"]] - ,[Plain [Str "f"]]] - ,[[Plain [Str "archie"]] - ,[Plain [Str "29"]] - ,[Plain [Str "m"]]] - ,[[Plain [Str "bella"]] - ,[Plain [Str "45"]] - ,[Plain [Str "f"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "name"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "age"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "sex"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "joan"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "24"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "f"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "archie"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "29"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "m"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "bella"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "45"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "f"]]]] + [] ,Para [Str "and",Space,Str "some",Space,Str "text",Space,Str "following",Space,Str "\8230"] ,Header 2 ("with-headers",[],[]) [Str "With",Space,Str "headers"] -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[Plain [Str "name"]] - ,[Plain [Str "age"]] - ,[Plain [Str "sex"]]] - [[[Plain [Str "joan"]] - ,[Plain [Str "24"]] - ,[Plain [Str "f"]]] - ,[[Plain [Str "archie"]] - ,[Plain [Str "29"]] - ,[Plain [Str "m"]]] - ,[[Plain [Str "bella"]] - ,[Plain [Str "45"]] - ,[Plain [Str "f"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "name"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "age"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "sex"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "joan"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "24"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "f"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "archie"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "29"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "m"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "bella"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "45"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "f"]]]] + [] ,Header 1 ("images",[],[]) [Str "Images"] ,Para [Str "Textile",Space,Str "inline",Space,Str "image",Space,Str "syntax,",Space,Str "like",LineBreak,Str "here",Space,Image ("",[],[]) [Str "this is the alt text"] ("this_is_an_image.png","this is the alt text"),LineBreak,Str "and",Space,Str "here",Space,Image ("",[],[]) [Str ""] ("this_is_an_image.png",""),Str "."] ,Header 1 ("attributes",[],[]) [Str "Attributes"] @@ -143,16 +183,30 @@ Pandoc (Meta {unMeta = fromList []}) ,Header 2 ("justified",[],[("lang","en"),("style","color:blue;text-align:justify;")]) [Str "Justified"] ,Para [Str "as",Space,Str "well",Space,Str "as",Space,Strong [Span ("",["foo"],[]) [Str "inline",Space,Str "attributes"]],Space,Str "of",Space,Span ("",[],[("style","color:red;")]) [Str "all",Space,Str "kind"]] ,Para [Str "and",Space,Str "paragraph",Space,Str "attributes,",Space,Str "and",Space,Str "table",Space,Str "attributes."] -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[] - ,[] - ,[]] - [[[Plain [Str "name"]] - ,[Plain [Str "age"]] - ,[Plain [Str "sex"]]] - ,[[Plain [Str "joan"]] - ,[Plain [Str "24"]] - ,[Plain [Str "f"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "name"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "age"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "sex"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "joan"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "24"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "f"]]]] + [] ,Para [Emph [Str "(class#id)",Space,Str "emph"]] ,Para [Emph [Str "(no",Space,Str "class#id)",Space,Str "emph"]] ,Header 1 ("entities",[],[]) [Str "Entities"] diff --git a/test/tikiwiki-reader.native b/test/tikiwiki-reader.native index 79dc4b708..f058c0815 100644 --- a/test/tikiwiki-reader.native +++ b/test/tikiwiki-reader.native @@ -90,41 +90,98 @@ Pandoc (Meta {unMeta = fromList []}) [[Plain [Str "five",Space,Str "sub",Space,Str "1",Space,Str "sub",Space,Str "1"]]]] ,[Plain [Str "five",Space,Str "sub",Space,Str "2"]]]]] ,Header 1 ("tables",[],[]) [Str "tables"] -,Table [] [AlignDefault,AlignDefault] [0.0,0.0] - [[Plain [Str ""]] - ,[Plain [Str ""]]] - [[[Plain [Str "Orange"]] - ,[Plain [Str "Apple"]]] - ,[[Plain [Str "Bread"]] - ,[Plain [Str "Pie"]]] - ,[[Plain [Str "Butter"]] - ,[Plain [Str "Ice",Space,Str "cream"]]]] -,Table [] [AlignDefault,AlignDefault] [0.0,0.0] - [[Plain [Str ""]] - ,[Plain [Str ""]]] - [[[Plain [Str "Orange"]] - ,[Plain [Str "Apple"]]] - ,[[Plain [Str "Bread"]] - ,[Plain [Str "Pie"]]] - ,[[Plain [Strong [Str "Butter"]]] - ,[Plain [Str "Ice",Space,Str "cream"]]]] -,Table [] [AlignDefault,AlignDefault] [0.0,0.0] - [[Plain [Str ""]] - ,[Plain [Str ""]]] - [[[Plain [Str "Orange"]] - ,[Plain [Str "Apple"]]] - ,[[Plain [Str "Bread",LineBreak,LineBreak,Str "and",Space,Str "cheese"]] - ,[Plain [Str "Pie",LineBreak,LineBreak,Strong [Str "apple"],Space,Str "and",Space,Emph [Str "carrot"],Space]]]] -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[Plain [Str ""]] - ,[Plain [Str ""]] - ,[Plain [Str ""]]] - [[[Plain [Space,Str "Orange",Space]] - ,[Plain [Space,Str "Apple",Space]] - ,[Plain [Space,Str "more"]]] - ,[[Plain [Space,Str "Bread",Space]] - ,[Plain [Space,Str "Pie",Space]] - ,[Plain [Space,Str "more"]]] - ,[[Plain [Space,Str "Butter",Space]] - ,[Plain [Space,Str "Ice",Space,Str "cream",Space]] - ,[Plain [Space,Str "and",Space,Str "more",Space]]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str ""]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str ""]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Orange"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Apple"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Bread"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Pie"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Butter"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Ice",Space,Str "cream"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str ""]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str ""]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Orange"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Apple"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Bread"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Pie"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Strong [Str "Butter"]]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Ice",Space,Str "cream"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str ""]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str ""]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Orange"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Apple"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Bread",LineBreak,LineBreak,Str "and",Space,Str "cheese"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Pie",LineBreak,LineBreak,Strong [Str "apple"],Space,Str "and",Space,Emph [Str "carrot"],Space]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str ""]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str ""]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str ""]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Space,Str "Orange",Space]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Space,Str "Apple",Space]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Space,Str "more"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Space,Str "Bread",Space]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Space,Str "Pie",Space]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Space,Str "more"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Space,Str "Butter",Space]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Space,Str "Ice",Space,Str "cream",Space]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Space,Str "and",Space,Str "more",Space]]]] + []] diff --git a/test/twiki-reader.native b/test/twiki-reader.native index 1447dcc3d..d100b5cd1 100644 --- a/test/twiki-reader.native +++ b/test/twiki-reader.native @@ -127,40 +127,91 @@ Pandoc (Meta {unMeta = fromList []}) ,[Plain [Str "and"]] ,[Plain [Str "supported"]]]]] ,Header 1 ("tables",[],[]) [Str "tables"] -,Table [] [AlignDefault,AlignDefault] [0.0,0.0] - [[] - ,[]] - [[[Plain [Str "Orange"]] - ,[Plain [Str "Apple"]]] - ,[[Plain [Str "Bread"]] - ,[Plain [Str "Pie"]]] - ,[[Plain [Str "Butter"]] - ,[Plain [Str "Ice",Space,Str "cream"]]]] -,Table [] [AlignLeft,AlignLeft] [0.0,0.0] - [[Plain [Str "Orange"]] - ,[Plain [Str "Apple"]]] - [[[Plain [Str "Bread"]] - ,[Plain [Str "Pie"]]] - ,[[Plain [Strong [Str "Butter"]]] - ,[Plain [Str "Ice",Space,Str "cream"]]]] -,Table [] [AlignLeft,AlignLeft] [0.0,0.0] - [[Plain [Str "Orange"]] - ,[Plain [Str "Apple"]]] - [[[Plain [Str "Bread",LineBreak,LineBreak,Str "and",Space,Str "cheese"]] - ,[Plain [Str "Pie",LineBreak,LineBreak,Strong [Str "apple"],Space,Str "and",Space,Emph [Str "carrot"]]]]] -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[] - ,[] - ,[]] - [[[Plain [Str "Orange"]] - ,[Plain [Str "Apple"]] - ,[Plain [Str "more"]]] - ,[[Plain [Str "Bread"]] - ,[Plain [Str "Pie"]] - ,[Plain [Str "more"]]] - ,[[Plain [Str "Butter"]] - ,[Plain [Str "Ice",Space,Str "cream"]] - ,[Plain [Str "and",Space,Str "more"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Orange"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Apple"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Bread"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Pie"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Butter"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Ice",Space,Str "cream"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignLeft,Nothing),(AlignLeft,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Orange"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Apple"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Bread"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Pie"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Strong [Str "Butter"]]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Ice",Space,Str "cream"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignLeft,Nothing),(AlignLeft,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Orange"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Apple"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Bread",LineBreak,LineBreak,Str "and",Space,Str "cheese"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Pie",LineBreak,LineBreak,Strong [Str "apple"],Space,Str "and",Space,Emph [Str "carrot"]]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Orange"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Apple"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "more"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Bread"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Pie"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "more"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Butter"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Ice",Space,Str "cream"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "and",Space,Str "more"]]]] + [] ,Header 1 ("macros",[],[]) [Str "macros"] ,Para [Span ("",["twiki-macro","TEST"],[]) []] ,Para [Span ("",["twiki-macro","TEST"],[]) [Str ""]] diff --git a/test/txt2tags.native b/test/txt2tags.native index f5134b8a1..356f9a9d6 100644 --- a/test/txt2tags.native +++ b/test/txt2tags.native @@ -301,308 +301,676 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "author"]] ,BulletList [[Plain [Str "just",Space,Str "like",Space,Str "when",Space,Str "using",Space,Str "the",Space,Str "two",Space,Str "blank",Space,Str "lines."]]]]]]] ,Header 1 ("table",[],[]) [Str "Table"] -,Table [] [AlignRight] [0.0] - [[]] - [[[Plain [Str "Cell",Space,Str "1"]]]] -,Table [] [AlignCenter,AlignCenter,AlignRight] [0.0,0.0,0.0] - [[] - ,[] - ,[]] - [[[Plain [Str "Cell",Space,Str "1"]] - ,[Plain [Str "Cell",Space,Str "2"]] - ,[Plain [Str "Cell",Space,Str "3"]]]] -,Table [] [AlignCenter,AlignCenter,AlignCenter] [0.0,0.0,0.0] - [[] - ,[] - ,[]] - [[[Plain [Str "Cell",Space,Str "1"]] - ,[Plain [Str "Cell",Space,Str "2"]] - ,[Plain [Str "Cell",Space,Str "3"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignRight,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "1"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignRight,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "3"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "3"]]]] + [] ,Para [Str "||",Space,Str "Cell",Space,Str "1",Space,Str "|",Space,Str "Cell",Space,Str "2",Space,Str "|",Space,Str "Cell",Space,Str "3",Space,Str "|"] -,Table [] [AlignCenter,AlignCenter,AlignCenter] [0.0,0.0,0.0] - [[] - ,[] - ,[]] - [[[Plain [Str "Cell",Space,Str "1"]] - ,[Plain [Str "Cell",Space,Str "2"]] - ,[Plain [Str "Cell",Space,Str "3"]]]] -,Table [] [AlignDefault,AlignCenter,AlignDefault] [0.0,0.0,0.0] - [[Plain [Str "Heading"]] - ,[Plain [Str "Heading"]] - ,[Plain [Str "Heading"]]] - [[[Plain [Str "<-"]] - ,[Plain [Str "--"]] - ,[Plain [Str "->"]]] - ,[[Plain [Str "--"]] - ,[Plain [Str "--"]] - ,[Plain [Str "--"]]] - ,[[Plain [Str "->"]] - ,[Plain [Str "--"]] - ,[Plain [Str "<-"]]]] -,Table [] [AlignDefault,AlignDefault,AlignCenter,AlignCenter] [0.0,0.0,0.0,0.0] - [[Plain [Str "1"]] - ,[Plain [Str "2"]] - ,[Plain [Str "3+4"]] - ,[]] - [[[Plain [Str "1"]] - ,[Plain [Str "2"]] - ,[Plain [Str "3"]] - ,[Plain [Str "4"]]] - ,[[Plain [Str "1+2+3"]] - ,[Plain [Str "4"]] - ,[] - ,[]] - ,[[Plain [Str "1"]] - ,[Plain [Str "2+3"]] - ,[Plain [Str "4"]] - ,[]] - ,[[Plain [Str "1+2+3+4"]] - ,[] - ,[] - ,[]]] -,Table [] [AlignCenter,AlignCenter,AlignCenter,AlignCenter] [0.0,0.0,0.0,0.0] - [[] - ,[] - ,[] - ,[]] - [[[Plain [Str "0"]] - ,[Plain [Str "1"]] - ,[Plain [Str "2"]] - ,[]] - ,[[Plain [Str "4"]] - ,[Plain [Str "5"]] - ,[] - ,[Plain [Str "7"]]] - ,[[Plain [Str "8"]] - ,[] - ,[Plain [Str "A"]] - ,[Plain [Str "B"]]] - ,[[] - ,[Plain [Str "D"]] - ,[Plain [Str "E"]] - ,[Plain [Str "F"]]]] -,Table [] [AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter] [0.0,0.0,0.0,0.0,0.0] - [[] - ,[] - ,[] - ,[] - ,[]] - [[[Plain [Str "1"]] - ,[] - ,[] - ,[] - ,[]] - ,[[Plain [Str "1"]] - ,[Plain [Str "2"]] - ,[] - ,[] - ,[]] - ,[[Plain [Str "1"]] - ,[Plain [Str "2"]] - ,[Plain [Str "3"]] - ,[] - ,[]] - ,[[Plain [Str "1"]] - ,[Plain [Str "2"]] - ,[Plain [Str "3"]] - ,[Plain [Str "4"]] - ,[]] - ,[[Plain [Str "1"]] - ,[Plain [Str "2"]] - ,[Plain [Str "3"]] - ,[Plain [Str "4"]] - ,[Plain [Str "5"]]]] -,Table [] [AlignDefault,AlignCenter,AlignCenter,AlignCenter,AlignCenter] [0.0,0.0,0.0,0.0,0.0] - [[] - ,[] - ,[] - ,[] - ,[]] - [[[Plain [Str "Jan"]] - ,[] - ,[] - ,[] - ,[]] - ,[[Plain [Str "Fev"]] - ,[] - ,[] - ,[] - ,[]] - ,[[Plain [Str "Mar"]] - ,[] - ,[] - ,[] - ,[]] - ,[[Plain [Str "Apr"]] - ,[] - ,[] - ,[] - ,[]] - ,[[Plain [Str "May"]] - ,[] - ,[] - ,[] - ,[]] - ,[[Plain [Str "20%"]] - ,[Plain [Str "40%"]] - ,[Plain [Str "60%"]] - ,[Plain [Str "80%"]] - ,[Plain [Str "100%"]]]] -,Table [] [AlignCenter,AlignDefault,AlignDefault,AlignCenter,AlignCenter] [0.0,0.0,0.0,0.0,0.0] - [[] - ,[] - ,[] - ,[] - ,[]] - [[[] - ,[] - ,[Plain [Str "/"]] - ,[] - ,[]] - ,[[] - ,[Plain [Str "/",Space,Str "/",Space,Str "/",Space,Str "/",Space,Str "/"]] - ,[] - ,[] - ,[]] - ,[[Plain [Str "/",Space,Str "/",Space,Str "/",Space,Str "/",Space,Str "/",Space,Str "/",Space,Str "/",Space,Str "/",Space,Str "/"]] - ,[] - ,[] - ,[] - ,[]] - ,[[] - ,[Plain [Str "o"]] - ,[] - ,[Plain [Str "o"]] - ,[]] - ,[[] - ,[] - ,[Plain [Str "."]] - ,[] - ,[]] - ,[[] - ,[Plain [Str "=",Space,Str "=",Space,Str "=",Space,Str "="]] - ,[] - ,[] - ,[]]] -,Table [] [AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter] [0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0] - [[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[]] - [[[Plain [Str "01"]] - ,[Plain [Str "02"]] - ,[] - ,[] - ,[Plain [Str "05"]] - ,[] - ,[Plain [Str "07"]] - ,[]] - ,[[] - ,[] - ,[Plain [Str "11"]] - ,[] - ,[Plain [Str "13"]] - ,[] - ,[] - ,[Plain [Str "16"]]] - ,[[Plain [Str "17"]] - ,[] - ,[Plain [Str "19"]] - ,[Plain [Str "20"]] - ,[] - ,[] - ,[Plain [Str "23"]] - ,[]] - ,[[Plain [Str "25"]] - ,[Plain [Str "26"]] - ,[] - ,[] - ,[Plain [Str "29"]] - ,[Plain [Str "30"]] - ,[] - ,[Plain [Str "32"]]] - ,[[] - ,[] - ,[Plain [Str "35"]] - ,[] - ,[Plain [Str "37"]] - ,[] - ,[Plain [Str "39"]] - ,[Plain [Str "40"]]]] -,Table [] [AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter] [0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0] - [[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[] - ,[]] - [[[Plain [Str "0"]] - ,[Plain [Str "1"]] - ,[Plain [Str "2"]] - ,[Plain [Str "3"]] - ,[Plain [Str "4"]] - ,[Plain [Str "5"]] - ,[Plain [Str "6"]] - ,[Plain [Str "7"]] - ,[Plain [Str "8"]] - ,[Plain [Str "9"]] - ,[Plain [Str "A"]] - ,[Plain [Str "B"]] - ,[Plain [Str "C"]] - ,[Plain [Str "D"]] - ,[Plain [Str "E"]] - ,[Plain [Str "F"]] - ,[Plain [Str "0"]] - ,[Plain [Str "1"]] - ,[Plain [Str "2"]] - ,[Plain [Str "3"]] - ,[Plain [Str "4"]] - ,[Plain [Str "5"]] - ,[Plain [Str "6"]] - ,[Plain [Str "7"]] - ,[Plain [Str "8"]] - ,[Plain [Str "9"]] - ,[Plain [Str "A"]] - ,[Plain [Str "B"]] - ,[Plain [Str "C"]] - ,[Plain [Str "D"]] - ,[Plain [Str "E"]] - ,[Plain [Str "F"]]]] -,Table [] [AlignCenter] [0.0] - [[]] - [[[]] - ,[[]] - ,[[]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Cell",Space,Str "3"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignCenter,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Heading"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Heading"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Heading"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "<-"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "--"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "->"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "--"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "--"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "--"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "->"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "--"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "<-"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3+4"]] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "4"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1+2+3"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2+3"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1+2+3+4"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "0"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "7"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "8"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "A"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "B"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "D"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "E"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "F"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Jan"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Fev"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Mar"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Apr"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "May"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "20%"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "40%"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "60%"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "80%"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "100%"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignCenter,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "/"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "/",Space,Str "/",Space,Str "/",Space,Str "/",Space,Str "/"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "/",Space,Str "/",Space,Str "/",Space,Str "/",Space,Str "/",Space,Str "/",Space,Str "/",Space,Str "/",Space,Str "/"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "o"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "o"]] + ,Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "."]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "=",Space,Str "=",Space,Str "=",Space,Str "="]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "01"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "02"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "05"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "07"]] + ,Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "11"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "13"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "16"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "17"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "19"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "20"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "23"]] + ,Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "25"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "26"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "29"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "30"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "32"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "35"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "37"]] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "39"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "40"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "0"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "6"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "7"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "8"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "9"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "A"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "B"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "C"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "D"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "E"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "F"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "0"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "3"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "4"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "5"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "6"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "7"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "8"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "9"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "A"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "B"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "C"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "D"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "E"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "F"]]]] + [] +,Table ("",[],[]) (Caption Nothing + []) [(AlignCenter,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + []] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + []]] + [] ,Para [Str "|this|is|not|a|table|"] ,Para [Str "|this|",Space,Str "is|",Space,Str "not|",Space,Str "a|",Space,Str "table|"] ,Para [Str "|this",Space,Str "|is",Space,Str "|not",Space,Str "|a",Space,Str "|table",Space,Str "|"] diff --git a/test/vimwiki-reader.native b/test/vimwiki-reader.native index 3b8c37c3a..5be4a8d5c 100644 --- a/test/vimwiki-reader.native +++ b/test/vimwiki-reader.native @@ -88,13 +88,24 @@ Pandoc (Meta {unMeta = fromList [("date",MetaInlines [Str "2017-05-01"]),("title ,Para [Math DisplayMath "a^2 + b^2 = c^2"] ,Plain [Str "and",Space,Str "some",Space,Str "preformatted",Space,Str "and",Space,Str "tables",Space,Str "belonging",Space,Str "to",Space,Str "item",Space,Str "1",Space,Str "as",Space,Str "well"] ,CodeBlock ("",[],[]) "I'm part of item 1." - ,Table [] [AlignDefault,AlignDefault] [0.0,0.0] - [[] - ,[]] - [[[Plain [Str "this",Space,Str "table"]] - ,[Plain [Str "is"]]] - ,[[Plain [Str "also",Space,Str "a",Space,Str "part"]] - ,[Plain [Str "of",Space,Str "item",Space,Str "1"]]]] + ,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "this",Space,Str "table"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "is"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "also",Space,Str "a",Space,Str "part"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "of",Space,Str "item",Space,Str "1"]]]] + [] ,Plain [Str "and",Space,Str "some",Space,Str "more",Space,Str "text",Space,Str "belonging",Space,Str "to",Space,Str "item",Space,Str "1."]] ,[Plain [Str "ordered",Space,Str "list",Space,Str "item",Space,Str "2"]]] ,BulletList @@ -181,11 +192,19 @@ Pandoc (Meta {unMeta = fromList [("date",MetaInlines [Str "2017-05-01"]),("title ,OrderedList (1,DefaultStyle,DefaultDelim) [[Plain [Span ("",["done3"],[]) [],Str "4",SoftBreak,Str "5"]] ,[Plain [Span ("",["done4"],[]) []] - ,Table [] [AlignDefault,AlignDefault] [0.0,0.0] - [[] - ,[]] - [[[Plain [Str "a"]] - ,[Plain [Str "b"]]]]]]] + ,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "a"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "b"]]]] + []]]] ,[Plain [Span ("",["done4"],[]) [],Str "task",Space,Str "2"]]] ,Header 2 ("math",[],[]) [Str "math"] ,Para [Math InlineMath " \\sum_i a_i^2 = 1 "] @@ -200,34 +219,71 @@ Pandoc (Meta {unMeta = fromList [("date",MetaInlines [Str "2017-05-01"]),("title ,Header 2 ("tags",[],[]) [Str "tags"] ,Para [Span ("-tag-one",[],[]) [Str ""],Span ("tag-one",["tag"],[]) [Str "tag-one"],Space,Span ("-tag-two",[],[]) [Str ""],Span ("tag-two",["tag"],[]) [Str "tag-two"]] ,Header 2 ("tables",[],[]) [Str "tables"] -,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] - [[Plain [Str "Year"]] - ,[Plain [Str "Temperature",Space,Str "(low)"]] - ,[Plain [Str "Temperature",Space,Str "(high)"]]] - [[[Plain [Str "1900"]] - ,[Plain [Str "-10"]] - ,[Plain [Str "25"]]] - ,[[Plain [Str "1910"]] - ,[Plain [Str "-15"]] - ,[Plain [Str "30"]]] - ,[[Plain [Str "1920"]] - ,[Plain [Str "-10"]] - ,[Plain [Str "32"]]] - ,[[Plain [Str "1930"]] - ,[Plain [Emph [Str "N/A"]]] - ,[Plain [Emph [Str "N/A"]]]] - ,[[Plain [Str "1940"]] - ,[Plain [Str "-2"]] - ,[Plain [Str "40"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Year"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Temperature",Space,Str "(low)"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "Temperature",Space,Str "(high)"]]]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1900"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "-10"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "25"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1910"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "-15"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "30"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1920"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "-10"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "32"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1930"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Emph [Str "N/A"]]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Emph [Str "N/A"]]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "1940"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "-2"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "40"]]]] + [] ,Header 3 ("centered headerless tables",[],[]) [Str "centered",Space,Str "headerless",Space,Str "tables"] ,Div ("",["center"],[]) - [Table [] [AlignDefault,AlignDefault] [0.0,0.0] - [[] - ,[]] - [[[Plain [Str "a"]] - ,[Plain [Str "b"]]] - ,[[Plain [Str "c"]] - ,[Plain [Str "d"]]]]] + [Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "a"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "b"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "c"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "d"]]]] + []] ,Header 2 ("paragraphs",[],[]) [Str "paragraphs"] ,Para [Str "This",Space,Str "is",Space,Str "first",Space,Str "paragraph",SoftBreak,Str "with",Space,Str "two",Space,Str "lines."] ,Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "second",Space,Str "paragraph",Space,Str "with",SoftBreak,Str "two",Space,Str "lines",Space,Str "after",Space,Str "many",Space,Str "blank",Space,Str "lines."] @@ -277,37 +333,78 @@ Pandoc (Meta {unMeta = fromList [("date",MetaInlines [Str "2017-05-01"]),("title ,Para [Span ("",["todo"],[]) [Str "TODO:"]] ,Header 1 ("not implemented yet",[],[]) [Emph [Span ("not implemented yet",[],[]) [],Strong [Str "not",Space,Str "implemented",Space,Str "yet"]]] ,Header 2 ("tables with spans",[],[]) [Str "tables",Space,Str "with",Space,Str "spans"] -,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0,0.0] - [[] - ,[] - ,[] - ,[]] - [[[Plain [Str "a"]] - ,[Plain [Str "b"]] - ,[Plain [Str "c"]] - ,[Plain [Str "d"]]] - ,[[Plain [Str "\\/"]] - ,[Plain [Str "e"]] - ,[Plain [Str ">"]] - ,[Plain [Str "f"]]] - ,[[Plain [Str "\\/"]] - ,[Plain [Str "\\/"]] - ,[Plain [Str ">"]] - ,[Plain [Str "g"]]] - ,[[Plain [Str "h"]] - ,[Plain [Str ">"]] - ,[Plain [Str ">"]] - ,[Plain [Str ">"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "a"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "b"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "c"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "d"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "\\/"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "e"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str ">"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "f"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "\\/"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "\\/"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str ">"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "g"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "h"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str ">"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str ">"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str ">"]]]] + [] ,Header 2 ("tables with multiple lines of headers",[],[]) [Str "tables",Space,Str "with",Space,Str "multiple",Space,Str "lines",Space,Str "of",Space,Str "headers"] -,Table [] [AlignDefault,AlignDefault] [0.0,0.0] - [[] - ,[]] - [[[Plain [Str "a"]] - ,[Plain [Str "b"]]] - ,[[Plain [Str "c"]] - ,[Plain [Str "d"]]] - ,[[Plain [Str "---"]] - ,[Plain [Str "---"]]]] +,Table ("",[],[]) (Caption Nothing + []) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0 + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [] + ,Cell ("",[],[]) Nothing 1 1 + []]] + [Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "a"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "b"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "c"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "d"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) Nothing 1 1 + [Plain [Str "---"]] + ,Cell ("",[],[]) Nothing 1 1 + [Plain [Str "---"]]]] + [] ,Header 2 ("some other placeholders",[],[]) [Str "some",Space,Str "other",Space,Str "placeholders"] ,Para [Code ("",[],[]) "template",Space,Str "placeholder",Space,Str "is",Space,Str "ignored."] ,Para [Code ("",[],[]) "nohtml",Space,Str "placeholder",Space,Str "is",Space,Str "ignored."]] |