diff options
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r-- | src/Text/Pandoc/Writers/OpenDocument.hs | 82 |
1 files changed, 56 insertions, 26 deletions
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index 731f98e75..c7ee839b5 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -32,11 +32,12 @@ import qualified Text.Pandoc.Builder as B import Text.Pandoc.Logging import Text.Pandoc.Options import Text.DocLayout -import Text.Pandoc.Shared (linesToPara, tshow) +import Text.Pandoc.Shared (linesToPara, tshow, blocksToInlines) import Text.Pandoc.Templates (renderTemplate) import qualified Text.Pandoc.Translations as Term (Term(Figure, Table)) import Text.Pandoc.Writers.Math import Text.Pandoc.Writers.Shared +import qualified Text.Pandoc.Writers.AnnotatedTable as Ann import Text.Pandoc.XML import Text.Printf (printf) @@ -371,9 +372,7 @@ blockToOpenDocument o bs | BulletList b <- bs = setFirstPara >> bulletListToOpenDocument o b | OrderedList a b <- bs = setFirstPara >> orderedList a b | CodeBlock _ s <- bs = setFirstPara >> preformatted s - | Table _ bc s th tb tf - <- bs = let (c, a, w, h, r) = toLegacyTable bc s th tb tf - in setFirstPara >> table c a w h r + | Table a bc s th tb tf <- bs = setFirstPara >> table (Ann.toTable a bc s th tb tf) | HorizontalRule <- bs = setFirstPara >> return (selfClosingTag "text:p" [ ("text:style-name", "Horizontal_20_Line") ]) | RawBlock f s <- bs = if f == Format "opendocument" @@ -396,29 +395,32 @@ blockToOpenDocument o bs orderedList a b = do (ln,pn) <- newOrderedListStyle (isTightList b) a inTags True "text:list" [ ("text:style-name", "L" <> tshow ln)] <$> orderedListToOpenDocument o pn b - table c a w h r = do + table :: PandocMonad m => Ann.Table -> OD m (Doc Text) + table (Ann.Table _ (Caption _ c) colspecs thead tbodies _) = do tn <- length <$> gets stTableStyles pn <- length <$> gets stParaStyles let genIds = map chr [65..] name = "Table" <> tshow (tn + 1) - columnIds = zip genIds w + (aligns, mwidths) = unzip colspecs + fromWidth (ColWidth w) | w > 0 = w + fromWidth _ = 0 + widths = map fromWidth mwidths + columnIds = zip genIds widths mkColumn n = selfClosingTag "table:table-column" [("table:style-name", name <> "." <> T.singleton (fst n))] columns = map mkColumn columnIds - paraHStyles = paraTableStyles "Heading" pn a - paraStyles = paraTableStyles "Contents" (pn + length (newPara paraHStyles)) a + paraHStyles = paraTableStyles "Heading" pn aligns + paraStyles = paraTableStyles "Contents" (pn + length (newPara paraHStyles)) aligns newPara = map snd . filter (not . isEmpty . snd) addTableStyle $ tableStyle tn columnIds mapM_ addParaStyle . newPara $ paraHStyles ++ paraStyles captionDoc <- if null c then return empty - else inlinesToOpenDocument o c >>= + else inlinesToOpenDocument o (blocksToInlines c) >>= if isEnabled Ext_native_numbering o then numberedTableCaption else unNumberedCaption "TableCaption" - th <- if all null h - then return empty - else colHeadsToOpenDocument o (map fst paraHStyles) h - tr <- mapM (tableRowToOpenDocument o (map fst paraStyles)) r + th <- colHeadsToOpenDocument o (map fst paraHStyles) thead + tr <- mapM (tableBodyToOpenDocument o (map fst paraStyles)) tbodies let tableDoc = inTags True "table:table" [ ("table:name" , name) , ("table:style-name", name) @@ -464,26 +466,54 @@ unNumberedCaption :: Monad m => Text -> Doc Text -> OD m (Doc Text) unNumberedCaption style caption = return $ inParagraphTagsWithStyle style caption colHeadsToOpenDocument :: PandocMonad m - => WriterOptions -> [Text] -> [[Block]] + => WriterOptions -> [Text] -> Ann.TableHead -> OD m (Doc Text) -colHeadsToOpenDocument o ns hs = - inTagsIndented "table:table-header-rows" . inTagsIndented "table:table-row" . vcat <$> - mapM (tableItemToOpenDocument o "TableHeaderRowCell") (zip ns hs) +colHeadsToOpenDocument o ns (Ann.TableHead _ hs) = + case hs of + [] -> return empty + (x:_) -> + let (Ann.HeaderRow _ _ c) = x + in inTagsIndented "table:table-header-rows" . + inTagsIndented "table:table-row" . + vcat <$> mapM (tableItemToOpenDocument o "TableHeaderRowCell") (zip ns c) + +tableBodyToOpenDocument:: PandocMonad m + => WriterOptions -> [Text] -> Ann.TableBody + -> OD m (Doc Text) +tableBodyToOpenDocument o ns tb = + let (Ann.TableBody _ _ _ r) = tb + in vcat <$> mapM (tableRowToOpenDocument o ns) r tableRowToOpenDocument :: PandocMonad m - => WriterOptions -> [Text] -> [[Block]] + => WriterOptions -> [Text] -> Ann.BodyRow -> OD m (Doc Text) -tableRowToOpenDocument o ns cs = - inTagsIndented "table:table-row" . vcat <$> - mapM (tableItemToOpenDocument o "TableRowCell") (zip ns cs) +tableRowToOpenDocument o ns r = + let (Ann.BodyRow _ _ _ c ) = r + in inTagsIndented "table:table-row" . vcat <$> + mapM (tableItemToOpenDocument o "TableRowCell") (zip ns c) + + +colspanAttrib :: ColSpan -> [(Text, Text)] +colspanAttrib cs = + case cs of + ColSpan 1 -> mempty + ColSpan n -> [("table:number-columns-spanned", tshow n)] + +rowspanAttrib :: RowSpan -> [(Text, Text)] +rowspanAttrib rs = + case rs of + RowSpan 1 -> mempty + RowSpan n -> [("table:number-rows-spanned", tshow n)] tableItemToOpenDocument :: PandocMonad m - => WriterOptions -> Text -> (Text,[Block]) + => WriterOptions -> Text -> (Text,Ann.Cell) -> OD m (Doc Text) -tableItemToOpenDocument o s (n,i) = - let a = [ ("table:style-name" , s ) - , ("office:value-type", "string" ) - ] +tableItemToOpenDocument o s (n,c) = + let (Ann.Cell _colspecs _colnum (Cell _ _ rs cs i) ) = c + csa = colspanAttrib cs + rsa = rowspanAttrib rs + a = [ ("table:style-name" , s ) + , ("office:value-type", "string" ) ] ++ csa ++ rsa in inTags True "table:table-cell" a <$> withParagraphStyle o n (map plainToPara i) |