diff options
-rw-r--r-- | src/Text/Pandoc/Writers/Docx/Table.hs | 31 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Docx/Types.hs | 2 | ||||
-rw-r--r-- | test/Tests/Writers/OOXML.hs | 4 | ||||
-rw-r--r-- | test/docx/golden/image.docx | bin | 26774 -> 26776 bytes |
4 files changed, 33 insertions, 4 deletions
diff --git a/src/Text/Pandoc/Writers/Docx/Table.hs b/src/Text/Pandoc/Writers/Docx/Table.hs index 49917e315..7a84c5278 100644 --- a/src/Text/Pandoc/Writers/Docx/Table.hs +++ b/src/Text/Pandoc/Writers/Docx/Table.hs @@ -17,7 +17,7 @@ import Control.Monad.State.Strict import Data.Array import Data.Text (Text) import Text.Pandoc.Definition -import Text.Pandoc.Class.PandocMonad (PandocMonad) +import Text.Pandoc.Class.PandocMonad (PandocMonad, translateTerm) import Text.Pandoc.Writers.Docx.Types import Text.Pandoc.Shared import Text.Printf (printf) @@ -25,6 +25,7 @@ import Text.Pandoc.Writers.GridTable hiding (Table) import Text.Pandoc.Writers.OOXML import Text.Pandoc.XML.Light as XML hiding (Attr) import qualified Data.Text as T +import qualified Text.Pandoc.Translations as Term import qualified Text.Pandoc.Writers.GridTable as Grid tableToOpenXML :: PandocMonad m @@ -33,15 +34,23 @@ tableToOpenXML :: PandocMonad m -> WS m [Content] tableToOpenXML blocksToOpenXML gridTable = do setFirstPara - let (Grid.Table _attr caption colspecs _rowheads thead tbodies tfoot) = + let (Grid.Table (ident,_,_) caption colspecs _rowheads thead tbodies tfoot) = gridTable let (Caption _maybeShortCaption captionBlocks) = caption + tablenum <- gets stNextTableNum + unless (null captionBlocks) $ + modify $ \st -> st{ stNextTableNum = tablenum + 1 } + let tableid = if T.null ident + then "table" <> tshow tablenum + else ident + tablename <- translateTerm Term.Table let captionStr = stringify captionBlocks let aligns = map fst $ elems colspecs captionXml <- if null captionBlocks then return [] else withParaPropM (pStyleM "Table Caption") - $ blocksToOpenXML captionBlocks + $ blocksToOpenXML + $ addLabel tableid tablename tablenum captionBlocks -- We set "in table" after processing the caption, because we don't -- want the "Table Caption" style to be overwritten with "Compact". modify $ \s -> s { stInTable = True } @@ -81,6 +90,22 @@ tableToOpenXML blocksToOpenXML gridTable = do modify $ \s -> s { stInTable = False } return $ captionXml ++ [Elem tbl] +addLabel :: Text -> Text -> Int -> [Block] -> [Block] +addLabel tableid tablename tablenum bs = + case bs of + (Para ils : rest) -> Para (label : Space : ils) : rest + (Plain ils : rest) -> Plain (label : Space : ils) : rest + _ -> Para [label] : bs + where + label = Span (tableid,[],[]) + [Str (tablename <> "\160"), + RawInline (Format "openxml") + ("<w:fldSimple w:instr=\"SEQ Table" + <> " \\* ARABIC \"><w:r><w:t>" + <> tshow tablenum + <> "</w:t></w:r></w:fldSimple>"), + Str ":"] + -- | Parts of a table data RowType = HeadRow | BodyRow | FootRow diff --git a/src/Text/Pandoc/Writers/Docx/Types.hs b/src/Text/Pandoc/Writers/Docx/Types.hs index 36ac45ad2..74b8d2753 100644 --- a/src/Text/Pandoc/Writers/Docx/Types.hs +++ b/src/Text/Pandoc/Writers/Docx/Types.hs @@ -118,6 +118,7 @@ data WriterState = WriterState{ , stDynamicTextProps :: Set.Set CharStyleName , stCurId :: Int , stNextFigureNum :: Int + , stNextTableNum :: Int } defaultWriterState :: WriterState @@ -139,6 +140,7 @@ defaultWriterState = WriterState{ , stDynamicTextProps = Set.empty , stCurId = 20 , stNextFigureNum = 1 + , stNextTableNum = 1 } setFirstPara :: PandocMonad m => WS m () diff --git a/test/Tests/Writers/OOXML.hs b/test/Tests/Writers/OOXML.hs index c1e47622d..83f05cfec 100644 --- a/test/Tests/Writers/OOXML.hs +++ b/test/Tests/Writers/OOXML.hs @@ -55,7 +55,9 @@ testArchive :: (WriterOptions -> Pandoc -> PandocIO BL.ByteString) -> IO Archive testArchive writerFn opts fp = do txt <- T.readFile fp - bs <- runIOorExplode $ readNative def txt >>= writerFn opts + bs <- runIOorExplode $ do + setTranslations "en-US" + readNative def txt >>= writerFn opts return $ toArchive bs compareFileList :: FilePath -> Archive -> Archive -> Maybe String diff --git a/test/docx/golden/image.docx b/test/docx/golden/image.docx Binary files differindex 9fe65326f..7c2d8a9ac 100644 --- a/test/docx/golden/image.docx +++ b/test/docx/golden/image.docx |