aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2013-08-03 23:05:14 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2013-08-03 23:05:14 -0700
commit4a84b78100f2cfa0f7f7d13a24693a37af60003d (patch)
treea9fc680a1a32fc3b9f50ff88fe9487569e391a5e /src
parent97b2be599e11bbe7aed73a30d8c7900f4276a3df (diff)
downloadpandoc-4a84b78100f2cfa0f7f7d13a24693a37af60003d.tar.gz
MediaWiki writer: Use native mediawiki tables instead of HTML.
Closes #720.
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Writers/MediaWiki.hs83
1 files changed, 39 insertions, 44 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