aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Docx.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers/Docx.hs')
-rw-r--r--src/Text/Pandoc/Readers/Docx.hs35
1 files changed, 21 insertions, 14 deletions
diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs
index f616a5b7a..bb86c91b0 100644
--- a/src/Text/Pandoc/Readers/Docx.hs
+++ b/src/Text/Pandoc/Readers/Docx.hs
@@ -72,12 +72,12 @@ import Data.Maybe (isJust, fromMaybe)
import Data.Sequence (ViewL (..), viewl)
import qualified Data.Sequence as Seq
import qualified Data.Set as Set
-import Text.Pandoc.Builder
+import Text.Pandoc.Builder as Pandoc
import Text.Pandoc.MediaBag (MediaBag)
import Text.Pandoc.Options
import Text.Pandoc.Readers.Docx.Combine
import Text.Pandoc.Readers.Docx.Lists
-import Text.Pandoc.Readers.Docx.Parse
+import Text.Pandoc.Readers.Docx.Parse as Docx
import Text.Pandoc.Shared
import Text.Pandoc.Walk
import Text.TeXMath (writeTeX)
@@ -494,13 +494,13 @@ singleParaToPlain blks
singleton $ Plain ils
singleParaToPlain blks = blks
-cellToBlocks :: PandocMonad m => Cell -> DocxContext m Blocks
-cellToBlocks (Cell bps) = do
+cellToBlocks :: PandocMonad m => Docx.Cell -> DocxContext m Blocks
+cellToBlocks (Docx.Cell bps) = do
blks <- smushBlocks <$> mapM bodyPartToBlocks bps
return $ fromList $ blocksToDefinitions $ blocksToBullets $ toList blks
-rowToBlocksList :: PandocMonad m => Row -> DocxContext m [Blocks]
-rowToBlocksList (Row cells) = do
+rowToBlocksList :: PandocMonad m => Docx.Row -> DocxContext m [Blocks]
+rowToBlocksList (Docx.Row cells) = do
blksList <- mapM cellToBlocks cells
return $ map singleParaToPlain blksList
@@ -645,7 +645,7 @@ bodyPartToBlocks (ListItem pPr _ _ _ parparts) =
bodyPartToBlocks (Tbl _ _ _ []) =
return $ para mempty
bodyPartToBlocks (Tbl cap _ look parts@(r:rs)) = do
- let caption = text cap
+ let cap' = simpleCaption $ plain $ text cap
(hdr, rows) = case firstRowFormatting look of
True | null rs -> (Nothing, [r])
| otherwise -> (Just r, rs)
@@ -659,16 +659,19 @@ bodyPartToBlocks (Tbl cap _ look parts@(r:rs)) = do
-- https://github.com/jgm/pandoc/pull/4361#issuecomment-365416155
nonEmpty [] = Nothing
nonEmpty l = Just l
- rowLength :: Row -> Int
- rowLength (Row c) = length c
+ rowLength :: Docx.Row -> Int
+ rowLength (Docx.Row c) = length c
+
+ let toRow = Pandoc.Row nullAttr . map simpleCell
+ toHeaderRow l = if null l then [] else [toRow l]
-- pad cells. New Text.Pandoc.Builder will do that for us,
-- so this is for compatibility while we switch over.
- let cells' = map (\row -> take width (row ++ repeat mempty)) cells
+ let cells' = map (\row -> toRow $ take width (row ++ repeat mempty)) cells
hdrCells <- case hdr of
- Just r' -> rowToBlocksList r'
- Nothing -> return $ replicate width mempty
+ Just r' -> toHeaderRow <$> rowToBlocksList r'
+ Nothing -> return []
-- The two following variables (horizontal column alignment and
-- relative column widths) go to the default at the
@@ -676,9 +679,13 @@ bodyPartToBlocks (Tbl cap _ look parts@(r:rs)) = do
-- so should be possible. Alignment might be more difficult,
-- since there doesn't seem to be a column entity in docx.
let alignments = replicate width AlignDefault
- widths = replicate width 0 :: [Double]
+ widths = replicate width ColWidthDefault
- return $ table caption (zip alignments widths) hdrCells cells'
+ return $ table cap'
+ (zip alignments widths)
+ (TableHead nullAttr hdrCells)
+ [TableBody nullAttr 0 [] cells']
+ (TableFoot nullAttr [])
bodyPartToBlocks (OMathPara e) =
return $ para $ displayMath (writeTeX e)