aboutsummaryrefslogtreecommitdiff
path: root/test/Tests/Readers
diff options
context:
space:
mode:
Diffstat (limited to 'test/Tests/Readers')
-rw-r--r--test/Tests/Readers/DokuWiki.hs6
-rw-r--r--test/Tests/Readers/LaTeX.hs2
-rw-r--r--test/Tests/Readers/Man.hs4
-rw-r--r--test/Tests/Readers/Muse.hs78
-rw-r--r--test/Tests/Readers/Org/Block/Table.hs8
-rw-r--r--test/Tests/Readers/Txt2Tags.hs6
6 files changed, 63 insertions, 41 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 ]