diff options
-rw-r--r-- | src/Text/Pandoc/Writers/MediaWiki.hs | 83 | ||||
-rw-r--r-- | tests/tables.mediawiki | 316 |
2 files changed, 164 insertions, 235 deletions
diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index b3b319c2a..e1bfd18b2 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -36,7 +36,7 @@ import Text.Pandoc.Shared import Text.Pandoc.Writers.Shared import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.XML ( escapeStringForXML ) -import Data.List ( intersect, intercalate ) +import Data.List ( intersect, intercalate, intersperse ) import Network.URI ( isURI ) import Control.Monad.State @@ -135,25 +135,17 @@ blockToMediaWiki opts (BlockQuote blocks) = do return $ "<blockquote>" ++ contents ++ "</blockquote>" blockToMediaWiki opts (Table capt aligns widths headers rows') = do - let alignStrings = map alignmentToString aligns - captionDoc <- if null capt - then return "" - else do - c <- inlineListToMediaWiki opts capt - return $ "<caption>" ++ c ++ "</caption>\n" - let percent w = show (truncate (100*w) :: Integer) ++ "%" - let coltags = if all (== 0.0) widths - then "" - else unlines $ map - (\w -> "<col width=\"" ++ percent w ++ "\" />") widths - head' <- if all null headers - then return "" - else do - hs <- tableRowToMediaWiki opts alignStrings 0 headers - return $ "<thead>\n" ++ hs ++ "\n</thead>\n" - body' <- zipWithM (tableRowToMediaWiki opts alignStrings) [1..] rows' - return $ "<table>\n" ++ captionDoc ++ coltags ++ head' ++ - "<tbody>\n" ++ unlines body' ++ "</tbody>\n</table>\n" + caption <- if null capt + then return "" + else do + c <- inlineListToMediaWiki opts capt + return $ "|+ " ++ trimr c ++ "\n" + let headless = all null headers + let allrows = if headless then rows' else headers:rows' + tableBody <- (concat . intersperse "|-\n") `fmap` + mapM (tableRowToMediaWiki opts headless aligns widths) + (zip [1..] allrows) + return $ "{|\n" ++ caption ++ tableBody ++ "|}\n" blockToMediaWiki opts x@(BulletList items) = do oldUseTags <- get >>= return . stUseTags @@ -285,20 +277,34 @@ vcat = intercalate "\n" -- Auxiliary functions for tables: tableRowToMediaWiki :: WriterOptions - -> [String] - -> Int - -> [[Block]] + -> Bool + -> [Alignment] + -> [Double] + -> (Int, [[Block]]) -> State WriterState String -tableRowToMediaWiki opts alignStrings rownum cols' = do - let celltype = if rownum == 0 then "th" else "td" - let rowclass = case rownum of - 0 -> "header" - x | x `rem` 2 == 1 -> "odd" - _ -> "even" - cols'' <- sequence $ zipWith - (\alignment item -> tableItemToMediaWiki opts celltype alignment item) - alignStrings cols' - return $ "<tr class=\"" ++ rowclass ++ "\">\n" ++ unlines cols'' ++ "</tr>" +tableRowToMediaWiki opts headless alignments widths (rownum, cells) = do + cells' <- mapM (\cellData -> + tableCellToMediaWiki opts headless rownum cellData) + $ zip3 alignments widths cells + return $ unlines cells' + +tableCellToMediaWiki :: WriterOptions + -> Bool + -> Int + -> (Alignment, Double, [Block]) + -> State WriterState String +tableCellToMediaWiki opts headless rownum (alignment, width, bs) = do + contents <- blockListToMediaWiki opts bs + let marker = if rownum == 1 && not headless then "!" else "|" + let percent w = show (truncate (100*w) :: Integer) ++ "%" + let attrs = ["align=" ++ show (alignmentToString alignment) | + alignment /= AlignDefault && alignment /= AlignLeft] ++ + ["width=\"" ++ percent width ++ "\"" | + width /= 0.0 && rownum == 1] + let attr = if null attrs + then "" + else unwords attrs ++ "|" + return $ marker ++ attr ++ trimr contents alignmentToString :: Alignment -> [Char] alignmentToString alignment = case alignment of @@ -307,17 +313,6 @@ alignmentToString alignment = case alignment of AlignCenter -> "center" AlignDefault -> "left" -tableItemToMediaWiki :: WriterOptions - -> String - -> String - -> [Block] - -> State WriterState String -tableItemToMediaWiki opts celltype align' item = do - let mkcell x = "<" ++ celltype ++ " align=\"" ++ align' ++ "\">" ++ - x ++ "</" ++ celltype ++ ">" - contents <- blockListToMediaWiki opts item - return $ mkcell contents - -- | Convert list of Pandoc block elements to MediaWiki. blockListToMediaWiki :: WriterOptions -- ^ Options -> [Block] -- ^ List of block elements diff --git a/tests/tables.mediawiki b/tests/tables.mediawiki index 4836ecd79..efde76559 100644 --- a/tests/tables.mediawiki +++ b/tests/tables.mediawiki @@ -1,212 +1,146 @@ Simple table with caption: -<table> -<caption>Demonstration of simple table syntax.</caption> -<thead> -<tr class="header"> -<th align="right">Right</th> -<th align="left">Left</th> -<th align="center">Center</th> -<th align="left">Default</th> -</tr> -</thead> -<tbody> -<tr class="odd"> -<td align="right">12</td> -<td align="left">12</td> -<td align="center">12</td> -<td align="left">12</td> -</tr> -<tr class="even"> -<td align="right">123</td> -<td align="left">123</td> -<td align="center">123</td> -<td align="left">123</td> -</tr> -<tr class="odd"> -<td align="right">1</td> -<td align="left">1</td> -<td align="center">1</td> -<td align="left">1</td> -</tr> -</tbody> -</table> +{| +|+ Demonstration of simple table syntax. +!align="right"|Right +!Left +!align="center"|Center +!Default +|- +|align="right"|12 +|12 +|align="center"|12 +|12 +|- +|align="right"|123 +|123 +|align="center"|123 +|123 +|- +|align="right"|1 +|1 +|align="center"|1 +|1 +|} Simple table without caption: -<table> -<thead> -<tr class="header"> -<th align="right">Right</th> -<th align="left">Left</th> -<th align="center">Center</th> -<th align="left">Default</th> -</tr> -</thead> -<tbody> -<tr class="odd"> -<td align="right">12</td> -<td align="left">12</td> -<td align="center">12</td> -<td align="left">12</td> -</tr> -<tr class="even"> -<td align="right">123</td> -<td align="left">123</td> -<td align="center">123</td> -<td align="left">123</td> -</tr> -<tr class="odd"> -<td align="right">1</td> -<td align="left">1</td> -<td align="center">1</td> -<td align="left">1</td> -</tr> -</tbody> -</table> +{| +!align="right"|Right +!Left +!align="center"|Center +!Default +|- +|align="right"|12 +|12 +|align="center"|12 +|12 +|- +|align="right"|123 +|123 +|align="center"|123 +|123 +|- +|align="right"|1 +|1 +|align="center"|1 +|1 +|} Simple table indented two spaces: -<table> -<caption>Demonstration of simple table syntax.</caption> -<thead> -<tr class="header"> -<th align="right">Right</th> -<th align="left">Left</th> -<th align="center">Center</th> -<th align="left">Default</th> -</tr> -</thead> -<tbody> -<tr class="odd"> -<td align="right">12</td> -<td align="left">12</td> -<td align="center">12</td> -<td align="left">12</td> -</tr> -<tr class="even"> -<td align="right">123</td> -<td align="left">123</td> -<td align="center">123</td> -<td align="left">123</td> -</tr> -<tr class="odd"> -<td align="right">1</td> -<td align="left">1</td> -<td align="center">1</td> -<td align="left">1</td> -</tr> -</tbody> -</table> +{| +|+ Demonstration of simple table syntax. +!align="right"|Right +!Left +!align="center"|Center +!Default +|- +|align="right"|12 +|12 +|align="center"|12 +|12 +|- +|align="right"|123 +|123 +|align="center"|123 +|123 +|- +|align="right"|1 +|1 +|align="center"|1 +|1 +|} Multiline table with caption: -<table> -<caption>Here's the caption. It may span multiple lines.</caption> -<col width="15%" /> -<col width="13%" /> -<col width="16%" /> -<col width="33%" /> -<thead> -<tr class="header"> -<th align="center">Centered Header</th> -<th align="left">Left Aligned</th> -<th align="right">Right Aligned</th> -<th align="left">Default aligned</th> -</tr> -</thead> -<tbody> -<tr class="odd"> -<td align="center">First</td> -<td align="left">row</td> -<td align="right">12.0</td> -<td align="left">Example of a row that spans multiple lines.</td> -</tr> -<tr class="even"> -<td align="center">Second</td> -<td align="left">row</td> -<td align="right">5.0</td> -<td align="left">Here's another one. Note the blank line between rows.</td> -</tr> -</tbody> -</table> +{| +|+ Here's the caption. It may span multiple lines. +!align="center" width="15%"|Centered Header +!width="13%"|Left Aligned +!align="right" width="16%"|Right Aligned +!width="33%"|Default aligned +|- +|align="center"|First +|row +|align="right"|12.0 +|Example of a row that spans multiple lines. +|- +|align="center"|Second +|row +|align="right"|5.0 +|Here's another one. Note the blank line between rows. +|} Multiline table without caption: -<table> -<col width="15%" /> -<col width="13%" /> -<col width="16%" /> -<col width="33%" /> -<thead> -<tr class="header"> -<th align="center">Centered Header</th> -<th align="left">Left Aligned</th> -<th align="right">Right Aligned</th> -<th align="left">Default aligned</th> -</tr> -</thead> -<tbody> -<tr class="odd"> -<td align="center">First</td> -<td align="left">row</td> -<td align="right">12.0</td> -<td align="left">Example of a row that spans multiple lines.</td> -</tr> -<tr class="even"> -<td align="center">Second</td> -<td align="left">row</td> -<td align="right">5.0</td> -<td align="left">Here's another one. Note the blank line between rows.</td> -</tr> -</tbody> -</table> +{| +!align="center" width="15%"|Centered Header +!width="13%"|Left Aligned +!align="right" width="16%"|Right Aligned +!width="33%"|Default aligned +|- +|align="center"|First +|row +|align="right"|12.0 +|Example of a row that spans multiple lines. +|- +|align="center"|Second +|row +|align="right"|5.0 +|Here's another one. Note the blank line between rows. +|} Table without column headers: -<table> -<tbody> -<tr class="odd"> -<td align="right">12</td> -<td align="left">12</td> -<td align="center">12</td> -<td align="right">12</td> -</tr> -<tr class="even"> -<td align="right">123</td> -<td align="left">123</td> -<td align="center">123</td> -<td align="right">123</td> -</tr> -<tr class="odd"> -<td align="right">1</td> -<td align="left">1</td> -<td align="center">1</td> -<td align="right">1</td> -</tr> -</tbody> -</table> +{| +|align="right"|12 +|12 +|align="center"|12 +|align="right"|12 +|- +|align="right"|123 +|123 +|align="center"|123 +|align="right"|123 +|- +|align="right"|1 +|1 +|align="center"|1 +|align="right"|1 +|} Multiline table without column headers: -<table> -<col width="15%" /> -<col width="13%" /> -<col width="16%" /> -<col width="33%" /> -<tbody> -<tr class="odd"> -<td align="center">First</td> -<td align="left">row</td> -<td align="right">12.0</td> -<td align="left">Example of a row that spans multiple lines.</td> -</tr> -<tr class="even"> -<td align="center">Second</td> -<td align="left">row</td> -<td align="right">5.0</td> -<td align="left">Here's another one. Note the blank line between rows.</td> -</tr> -</tbody> -</table> +{| +|align="center" width="15%"|First +|width="13%"|row +|align="right" width="16%"|12.0 +|width="33%"|Example of a row that spans multiple lines. +|- +|align="center"|Second +|row +|align="right"|5.0 +|Here's another one. Note the blank line between rows. +|} |