aboutsummaryrefslogtreecommitdiff
path: root/test/Tests
diff options
context:
space:
mode:
authordespresc <christian.j.j.despres@gmail.com>2020-04-04 16:35:42 -0400
committerdespresc <christian.j.j.despres@gmail.com>2020-04-15 23:03:22 -0400
commit4e34d366df31937cdc69b6b366355f10a84c16b2 (patch)
tree844503b0f59439acaec5d2f8e2f016e2eb1d214c /test/Tests
parentf8ce38975b547fe7fc8c12ccee3a940b35d8b9cf (diff)
downloadpandoc-4e34d366df31937cdc69b6b366355f10a84c16b2.tar.gz
Adapt to the newest Table type, fix some previous adaptation issues
- Writers.Native is now adapted to the new Table type. - Inline captions should now be conditionally wrapped in a Plain, not a Para block. - The toLegacyTable function now lives in Writers.Shared.
Diffstat (limited to 'test/Tests')
-rw-r--r--test/Tests/Readers/DokuWiki.hs18
-rw-r--r--test/Tests/Readers/LaTeX.hs2
-rw-r--r--test/Tests/Readers/Man.hs8
-rw-r--r--test/Tests/Readers/Muse.hs76
-rw-r--r--test/Tests/Readers/Org/Block/Table.hs10
-rw-r--r--test/Tests/Readers/Txt2Tags.hs10
-rw-r--r--test/Tests/Writers/ConTeXt.hs2
-rw-r--r--test/Tests/Writers/Muse.hs4
8 files changed, 80 insertions, 50 deletions
diff --git a/test/Tests/Readers/DokuWiki.hs b/test/Tests/Readers/DokuWiki.hs
index 52b4764a5..d812c215f 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, Nothing), (AlignDefault, Nothing)]
+ table mempty [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
[]
[[plain "foo", plain "bar"]
,[plain "bat", plain "baz"]]
@@ -304,7 +304,7 @@ tests = [ testGroup "inlines"
T.unlines [ "^ foo ^ bar ^"
, "| bat | baz |"
] =?>
- table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
+ table mempty [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
[plain "foo", plain "bar"]
[[plain "bat", plain "baz"]]
, "Table with colspan" =:
@@ -312,11 +312,15 @@ tests = [ testGroup "inlines"
, "| 1,0 | 1,1 ||"
, "| 2,0 | 2,1 | 2,2 |"
] =?>
- 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"]
- ]
+ table
+ mempty
+ [(AlignDefault, ColWidthDefault)
+ ,(AlignDefault, ColWidthDefault)
+ ,(AlignDefault, ColWidthDefault)]
+ [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"]
+ ]
, "Indented code block" =:
T.unlines [ "foo"
, " bar"
diff --git a/test/Tests/Readers/LaTeX.hs b/test/Tests/Readers/LaTeX.hs
index 098848769..5cddab871 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 Nothing))
+simpleTable' aligns = table "" (zip aligns (repeat ColWidthDefault))
(map (const mempty) aligns)
tokUntokRt :: String -> Bool
diff --git a/test/Tests/Readers/Man.hs b/test/Tests/Readers/Man.hs
index f358630bb..7623dcb71 100644
--- a/test/Tests/Readers/Man.hs
+++ b/test/Tests/Readers/Man.hs
@@ -122,12 +122,16 @@ tests = [
testGroup "Tables" [
"t1" =:
".TS\nallbox;\nl l l.\na\tb\tc\nd\te\tf\n.TE"
- =?> table mempty (replicate 3 (AlignLeft, Nothing)) [] [
+ =?> table mempty (replicate 3 (AlignLeft, ColWidthDefault)) [] [
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, Nothing)] [] [[plain $ text "a b c d"], [plain $ str "f"]]
+ =?> table
+ mempty
+ [(AlignRight, ColWidthDefault)]
+ []
+ [[plain $ text "a b c d"], [plain $ str "f"]]
]
]
diff --git a/test/Tests/Readers/Muse.hs b/test/Tests/Readers/Muse.hs
index abf9e1ced..074b2dc27 100644
--- a/test/Tests/Readers/Muse.hs
+++ b/test/Tests/Readers/Muse.hs
@@ -15,7 +15,6 @@ 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
@@ -26,7 +25,8 @@ import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
-import Text.Pandoc.Shared (underlineSpan, toLegacyTable)
+import Text.Pandoc.Shared (underlineSpan)
+import Text.Pandoc.Writers.Shared (toLegacyTable)
import Text.Pandoc.Walk
amuse :: Text -> Pandoc
@@ -46,31 +46,31 @@ spcSep = mconcat . intersperse space
-- Tables don't round-trip yet
--
makeRoundTrip :: Block -> Block
-makeRoundTrip t@(Table tattr blkCapt specs rhs thead tbody tfoot) =
+makeRoundTrip t@(Table tattr blkCapt specs thead tbody tfoot) =
if isSimple && numcols > 1
then t
else Para [Str "table was here"]
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 = and [ hasSimpleCells
+ isSimple = and [ isSimpleHead thead
+ , isSimpleBodies tbody
+ , isSimpleFoot tfoot
, all (== 0) widths
- , null tfoot
- , length thead == 1
, isNullAttr tattr
- , rhs == 0
, simpleCapt ]
isNullAttr ("", [], []) = True
isNullAttr _ = False
+ isAlignDefault AlignDefault = True
+ isAlignDefault _ = 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
+ , isAlignDefault ali
, isSimpleCellBody body ]
isSimpleCellBody [Plain ils] = not (hasLineBreak ils)
isSimpleCellBody [Para ils ] = not (hasLineBreak ils)
@@ -80,6 +80,16 @@ makeRoundTrip t@(Table tattr blkCapt specs rhs thead tbody tfoot) =
Caption Nothing [Para _] -> True
Caption Nothing [Plain _] -> True
_ -> False
+ isSimpleHead (TableHead attr [r])
+ = isNullAttr attr && isSimpleRow r
+ isSimpleHead _ = False
+ isSimpleBody (TableBody attr rhc hd bd) = and [ isNullAttr attr
+ , rhc == 0
+ , null hd
+ , all isSimpleRow bd ]
+ isSimpleBodies [b] = isSimpleBody b
+ isSimpleBodies _ = False
+ isSimpleFoot (TableFoot attr rs) = isNullAttr attr && null rs
makeRoundTrip (OrderedList (start, LowerAlpha, _) items) = OrderedList (start, Decimal, Period) items
makeRoundTrip (OrderedList (start, UpperAlpha, _) items) = OrderedList (start, Decimal, Period) items
@@ -972,12 +982,12 @@ tests =
, testGroup "Tables"
[ "Two cell table" =:
"One | Two" =?>
- table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
+ table mempty [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
[]
[[plain "One", plain "Two"]]
, "Table with multiple words" =:
"One two | three four" =?>
- table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
+ table mempty [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
[]
[[plain "One two", plain "three four"]]
, "Not a table" =:
@@ -991,7 +1001,7 @@ tests =
[ "One | Two"
, "Three | Four"
] =?>
- table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
+ table mempty [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
[]
[[plain "One", plain "Two"],
[plain "Three", plain "Four"]]
@@ -1000,7 +1010,7 @@ tests =
[ "First || Second"
, "Third | Fourth"
] =?>
- table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
+ table mempty [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
[plain "First", plain "Second"]
[[plain "Third", plain "Fourth"]]
, "Table with two headers" =:
@@ -1009,7 +1019,7 @@ tests =
, "Second || header"
, "Foo | bar"
] =?>
- table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
+ table mempty [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
[plain "First", plain "header"]
[[plain "Second", plain "header"],
[plain "Foo", plain "bar"]]
@@ -1019,7 +1029,7 @@ tests =
, "Baz || foo"
, "Bar | baz"
] =?>
- table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
+ table mempty [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
[plain "Baz", plain "foo"]
[[plain "Bar", plain "baz"],
[plain "Foo", plain "bar"]]
@@ -1030,7 +1040,7 @@ tests =
, "Second | row | there"
, "|+ Table caption +|"
] =?>
- table (text "Table caption") (replicate 3 (AlignDefault, Nothing))
+ table (text "Table caption") (replicate 3 (AlignDefault, ColWidthDefault))
[plain "Foo", plain "bar", plain "baz"]
[[plain "First", plain "row", plain "here"],
[plain "Second", plain "row", plain "there"]]
@@ -1039,7 +1049,7 @@ tests =
[ "Foo | bar"
, "|+ Table + caption +|"
] =?>
- table (text "Table + caption") (replicate 2 (AlignDefault, Nothing))
+ table (text "Table + caption") (replicate 2 (AlignDefault, ColWidthDefault))
[]
[[plain "Foo", plain "bar"]]
, "Caption without table" =:
@@ -1051,7 +1061,7 @@ tests =
, " Baz | foo"
, " Bar | baz"
] =?>
- table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
+ table mempty [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
[]
[[plain "Foo", plain "bar"],
[plain "Baz", plain "foo"],
@@ -1063,7 +1073,7 @@ tests =
, " bar |"
, " || baz"
] =?>
- table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
+ table mempty [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
[plain "", plain "baz"]
[[plain "", plain "Foo"],
[plain "", plain ""],
@@ -1074,7 +1084,8 @@ tests =
, " 4 | | 6"
, " 7 | 8 | 9"
] =?>
- table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing), (AlignDefault, Nothing)]
+ table mempty [ (AlignDefault, ColWidthDefault)
+ , (AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
[]
[[plain "1", plain "2", plain "3"],
[plain "4", mempty, plain "6"],
@@ -1085,7 +1096,7 @@ tests =
, "| foo | bar |"
, "+-----+-----+"
] =?>
- table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
+ table mempty [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
[]
[[para "foo", para "bar"]]
, "Grid table inside list" =:
@@ -1094,7 +1105,8 @@ tests =
, " | foo | bar |"
, " +-----+-----+"
] =?>
- bulletList [table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
+ bulletList [table mempty [ (AlignDefault, ColWidthDefault)
+ , (AlignDefault, ColWidthDefault)]
[]
[[para "foo", para "bar"]]]
, "Grid table with two rows" =:
@@ -1105,7 +1117,7 @@ tests =
, "| bat | baz |"
, "+-----+-----+"
] =?>
- table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
+ table mempty [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
[]
[[para "foo", para "bar"]
,[para "bat", para "baz"]]
@@ -1117,9 +1129,9 @@ tests =
, "|+---+|"
, "+-----+"
] =?>
- table mempty [(AlignDefault, Nothing)]
+ table mempty [(AlignDefault, ColWidthDefault)]
[]
- [[table mempty [(AlignDefault, Nothing)]
+ [[table mempty [(AlignDefault, ColWidthDefault)]
[]
[[para "foo"]]]]
, "Grid table with example" =:
@@ -1130,7 +1142,7 @@ tests =
, "| </example> |"
, "+------------+"
] =?>
- table mempty [(AlignDefault, Nothing)]
+ table mempty [(AlignDefault, ColWidthDefault)]
[]
[[codeBlock "foo"]]
]
@@ -1501,15 +1513,19 @@ tests =
]
, "Definition list with table" =:
" foo :: bar | baz" =?>
- definitionList [ ("foo", [ table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
+ definitionList [ ("foo", [ table mempty [ (AlignDefault, ColWidthDefault)
+ , (AlignDefault, ColWidthDefault)]
[]
[[plain "bar", plain "baz"]]
])]
, "Definition list with table inside bullet list" =:
" - foo :: bar | baz" =?>
- bulletList [definitionList [ ("foo", [ table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
- []
- [[plain "bar", plain "baz"]]
+ bulletList [definitionList [ ("foo", [ table
+ mempty
+ [ (AlignDefault, ColWidthDefault)
+ , (AlignDefault, ColWidthDefault) ]
+ []
+ [[plain "bar", plain "baz"]]
])]]
, test emacsMuse "Multi-line definition lists from Emacs Muse manual"
(T.unlines
diff --git a/test/Tests/Readers/Org/Block/Table.hs b/test/Tests/Readers/Org/Block/Table.hs
index c09abcd0d..4b76f4a58 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, Nothing))
+simpleTable' n = table "" (replicate n (AlignDefault, ColWidthDefault))
tests :: [TestTree]
tests =
@@ -121,7 +121,9 @@ tests =
, "| 1 | One | foo |"
, "| 2 | Two | bar |"
] =?>
- table "" (zip [AlignCenter, AlignRight, AlignDefault] [Nothing, Nothing, Nothing])
+ table "" (zip
+ [AlignCenter, AlignRight, AlignDefault]
+ [ColWidthDefault, ColWidthDefault, ColWidthDefault])
[]
[ [ plain "Numbers", plain "Text", plain "More" ]
, [ plain "1" , plain "One" , plain "foo" ]
@@ -143,7 +145,7 @@ tests =
, "| 1 | One | foo |"
, "| 2"
] =?>
- table "" (zip [AlignCenter, AlignRight] [Nothing, Nothing])
+ table "" (zip [AlignCenter, AlignRight] [ColWidthDefault, ColWidthDefault])
[ plain "Numbers", plain "Text" ]
[ [ plain "1" , plain "One" , plain "foo" ]
, [ plain "2" ]
@@ -155,7 +157,7 @@ tests =
, "| 9 | 42 |"
] =?>
table "Hitchhiker's Multiplication Table"
- [(AlignDefault, Nothing), (AlignDefault, Nothing)]
+ [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
[]
[ [ plain "x", plain "6" ]
, [ plain "9", plain "42" ]
diff --git a/test/Tests/Readers/Txt2Tags.hs b/test/Tests/Readers/Txt2Tags.hs
index e9ee6729c..be6747bfe 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, Nothing))
+simpleTable' n = table "" (replicate n (AlignCenter, ColWidthDefault))
tests :: [TestTree]
tests =
@@ -398,7 +398,9 @@ tests =
, "| 1 | One | foo |"
, "| 2 | Two | bar |"
] =?>
- table "" (zip [AlignCenter, AlignRight, AlignDefault] [Nothing, Nothing, Nothing])
+ table "" (zip
+ [AlignCenter, AlignRight, AlignDefault]
+ [ColWidthDefault, ColWidthDefault, ColWidthDefault])
[]
[ [ plain "Numbers", plain "Text", plain "More" ]
, [ plain "1" , plain "One" , plain "foo" ]
@@ -415,7 +417,9 @@ tests =
, "| 1 | One | foo |"
, "| 2 "
] =?>
- table "" (zip [AlignCenter, AlignLeft, AlignLeft] [Nothing, Nothing, Nothing])
+ table "" (zip
+ [AlignCenter, AlignLeft, AlignLeft]
+ [ColWidthDefault, ColWidthDefault, ColWidthDefault])
[ 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 ea717b48e..cc90b95a9 100644
--- a/test/Tests/Writers/ConTeXt.hs
+++ b/test/Tests/Writers/ConTeXt.hs
@@ -99,7 +99,7 @@ tests = [ testGroup "inline code"
, testGroup "natural tables"
[ test contextNtb "table with header and caption" $
let capt = text "Table 1"
- aligns = [(AlignRight, Nothing), (AlignLeft, Nothing), (AlignCenter, Nothing), (AlignDefault, Nothing)]
+ aligns = [(AlignRight, ColWidthDefault), (AlignLeft, ColWidthDefault), (AlignCenter, ColWidthDefault), (AlignDefault, ColWidthDefault)]
headers = [plain $ text "Right",
plain $ text "Left",
plain $ text "Center",
diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs
index ba5fdf94f..42748ad85 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,Nothing),(AlignDefault,Nothing)]
+ in table mempty [(AlignDefault,ColWidthDefault),(AlignDefault,ColWidthDefault)]
[mempty, mempty] rows
=?>
unlines [ " Para 1.1 | Para 1.2"
@@ -393,7 +393,7 @@ tests = [ testGroup "block elements"
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 capt [(AlignDefault,Nothing),(AlignDefault,Nothing)]
+ in table capt [(AlignDefault,ColWidthDefault),(AlignDefault,ColWidthDefault)]
headers rows
=?> unlines [ " header 1 || header 2"
, " Para 1.1 | Para 1.2"