aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Readers/Docx.hs92
-rw-r--r--src/Text/Pandoc/Readers/Docx/Parse.hs113
-rw-r--r--src/Text/Pandoc/Readers/Docx/Util.hs7
-rw-r--r--test/Tests/Readers/Docx.hs16
-rw-r--r--test/docx/sdt_elements.native13
-rw-r--r--test/docx/table_captions_no_field.docxbin0 -> 40482 bytes
-rw-r--r--test/docx/table_captions_no_field.native34
-rw-r--r--test/docx/table_captions_with_field.docxbin0 -> 41091 bytes
-rw-r--r--test/docx/table_captions_with_field.native54
-rw-r--r--test/docx/table_header_rowspan.docxbin0 -> 15826 bytes
-rw-r--r--test/docx/table_header_rowspan.native189
-rw-r--r--test/docx/table_one_header_row.docxbin0 -> 12185 bytes
-rw-r--r--test/docx/table_one_header_row.native18
-rw-r--r--test/docx/table_one_row.docxbin25251 -> 12148 bytes
-rw-r--r--test/docx/table_variable_width.native19
15 files changed, 487 insertions, 68 deletions
diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs
index 375bb7338..c06adf7e3 100644
--- a/src/Text/Pandoc/Readers/Docx.hs
+++ b/src/Text/Pandoc/Readers/Docx.hs
@@ -61,13 +61,14 @@ module Text.Pandoc.Readers.Docx
import Codec.Archive.Zip
import Control.Monad.Reader
import Control.Monad.State.Strict
+import Data.Bifunctor (bimap, first)
import qualified Data.ByteString.Lazy as B
import Data.Default (Default)
-import Data.List (delete, intersect)
+import Data.List (delete, intersect, foldl')
import Data.Char (isSpace)
import qualified Data.Map as M
import qualified Data.Text as T
-import Data.Maybe (isJust, fromMaybe)
+import Data.Maybe (catMaybes, isJust, fromMaybe)
import Data.Sequence (ViewL (..), viewl)
import qualified Data.Sequence as Seq
import qualified Data.Set as Set
@@ -113,6 +114,7 @@ data DState = DState { docxAnchorMap :: M.Map T.Text T.Text
-- restarting
, docxListState :: M.Map (T.Text, T.Text) Integer
, docxPrevPara :: Inlines
+ , docxTableCaptions :: [Blocks]
}
instance Default DState where
@@ -123,6 +125,7 @@ instance Default DState where
, docxDropCap = mempty
, docxListState = M.empty
, docxPrevPara = mempty
+ , docxTableCaptions = []
}
data DEnv = DEnv { docxOptions :: ReaderOptions
@@ -491,15 +494,32 @@ singleParaToPlain blks
singleton $ Plain ils
singleParaToPlain blks = blks
-cellToBlocks :: PandocMonad m => Docx.Cell -> DocxContext m Blocks
-cellToBlocks (Docx.Cell bps) = do
+cellToCell :: PandocMonad m => RowSpan -> Docx.Cell -> DocxContext m Pandoc.Cell
+cellToCell rowSpan (Docx.Cell gridSpan _ bps) = do
blks <- smushBlocks <$> mapM bodyPartToBlocks bps
- return $ fromList $ blocksToDefinitions $ blocksToBullets $ toList blks
+ let blks' = singleParaToPlain $ fromList $ blocksToDefinitions $ blocksToBullets $ toList blks
+ return (cell AlignDefault rowSpan (ColSpan (fromIntegral gridSpan)) blks')
+
+rowsToRows :: PandocMonad m => [Docx.Row] -> DocxContext m [Pandoc.Row]
+rowsToRows rows = do
+ let rowspans = (fmap . fmap) (first RowSpan) (Docx.rowsToRowspans rows)
+ cells <- traverse (traverse (uncurry cellToCell)) rowspans
+ return (fmap (Pandoc.Row nullAttr) cells)
+
+splitHeaderRows :: Bool -> [Docx.Row] -> ([Docx.Row], [Docx.Row])
+splitHeaderRows hasFirstRowFormatting rs = bimap reverse reverse $ fst
+ $ if hasFirstRowFormatting
+ then foldl' f ((take 1 rs, []), True) (drop 1 rs)
+ else foldl' f (([], []), False) rs
+ where
+ f ((headerRows, bodyRows), previousRowWasHeader) r@(Docx.Row h cs)
+ | h == HasTblHeader || (previousRowWasHeader && any isContinuationCell cs)
+ = ((r : headerRows, bodyRows), True)
+ | otherwise
+ = ((headerRows, r : bodyRows), False)
+
+ isContinuationCell (Docx.Cell _ vm _) = vm == Docx.Continue
-rowToBlocksList :: PandocMonad m => Docx.Row -> DocxContext m [Blocks]
-rowToBlocksList (Docx.Row cells) = do
- blksList <- mapM cellToBlocks cells
- return $ map singleParaToPlain blksList
-- like trimInlines, but also take out linebreaks
trimSps :: Inlines -> Inlines
@@ -546,6 +566,11 @@ normalizeToClassName = T.map go . fromStyleName
where go c | isSpace c = '-'
| otherwise = c
+bodyPartToTableCaption :: PandocMonad m => BodyPart -> DocxContext m (Maybe Blocks)
+bodyPartToTableCaption (TblCaption pPr parparts) =
+ Just <$> bodyPartToBlocks (Paragraph pPr parparts)
+bodyPartToTableCaption _ = pure Nothing
+
bodyPartToBlocks :: PandocMonad m => BodyPart -> DocxContext m Blocks
bodyPartToBlocks (Paragraph pPr parparts)
| Just True <- pBidi pPr = do
@@ -637,50 +662,43 @@ bodyPartToBlocks (ListItem pPr _ _ _ parparts) =
let pPr' = pPr {pStyle = constructBogusParStyleData "list-paragraph": pStyle pPr}
in
bodyPartToBlocks $ Paragraph pPr' parparts
+bodyPartToBlocks (TblCaption _ _) =
+ return $ para mempty -- collected separately
bodyPartToBlocks (Tbl _ _ _ []) =
return $ para mempty
-bodyPartToBlocks (Tbl cap grid look parts@(r:rs)) = do
- let cap' = simpleCaption $ plain $ text cap
- (hdr, rows) = case firstRowFormatting look of
- True | null rs -> (Nothing, [r])
- | otherwise -> (Just r, rs)
- False -> (Nothing, r:rs)
-
- cells <- mapM rowToBlocksList rows
+bodyPartToBlocks (Tbl cap grid look parts) = do
+ captions <- gets docxTableCaptions
+ fullCaption <- case captions of
+ c : cs -> do
+ modify (\s -> s { docxTableCaptions = cs })
+ return c
+ [] -> return $ if T.null cap then mempty else plain (text cap)
+ let shortCaption = if T.null cap then Nothing else Just (toList (text cap))
+ cap' = caption shortCaption fullCaption
+ (hdr, rows) = splitHeaderRows (firstRowFormatting look) parts
let width = maybe 0 maximum $ nonEmpty $ map rowLength parts
rowLength :: Docx.Row -> Int
- rowLength (Docx.Row c) = length c
+ rowLength (Docx.Row _ c) = sum (fmap (\(Docx.Cell gridSpan _ _) -> fromIntegral gridSpan) c)
- let toRow = Pandoc.Row nullAttr . map simpleCell
- toHeaderRow l = [toRow l | not (null l)]
+ headerCells <- rowsToRows hdr
+ bodyCells <- rowsToRows rows
- -- pad cells. New Text.Pandoc.Builder will do that for us,
- -- so this is for compatibility while we switch over.
- let cells' = map (\row -> toRow $ take width (row ++ repeat mempty)) cells
-
- hdrCells <- case hdr of
- Just r' -> toHeaderRow <$> rowToBlocksList r'
- Nothing -> return []
-
- -- The two following variables (horizontal column alignment and
- -- relative column widths) go to the default at the
- -- moment. Width information is in the TblGrid field of the Tbl,
- -- so should be possible. Alignment might be more difficult,
- -- since there doesn't seem to be a column entity in docx.
+ -- Horizontal column alignment goes to the default at the moment. Getting
+ -- it might be difficult, since there doesn't seem to be a column entity
+ -- in docx.
let alignments = replicate width AlignDefault
totalWidth = sum grid
widths = (\w -> ColWidth (fromInteger w / fromInteger totalWidth)) <$> grid
return $ table cap'
(zip alignments widths)
- (TableHead nullAttr hdrCells)
- [TableBody nullAttr 0 [] cells']
+ (TableHead nullAttr headerCells)
+ [TableBody nullAttr 0 [] bodyCells]
(TableFoot nullAttr [])
bodyPartToBlocks (OMathPara e) =
return $ para $ displayMath (writeTeX e)
-
-- replace targets with generated anchors.
rewriteLink' :: PandocMonad m => Inline -> DocxContext m Inline
rewriteLink' l@(Link attr ils (T.uncons -> Just ('#',target), title)) = do
@@ -716,6 +734,8 @@ bodyToOutput :: PandocMonad m => Body -> DocxContext m (Meta, [Block])
bodyToOutput (Body bps) = do
let (metabps, blkbps) = sepBodyParts bps
meta <- bodyPartsToMeta metabps
+ captions <- catMaybes <$> mapM bodyPartToTableCaption blkbps
+ modify (\s -> s { docxTableCaptions = captions })
blks <- smushBlocks <$> mapM bodyPartToBlocks blkbps
blks' <- rewriteLinks $ blocksToDefinitions $ blocksToBullets $ toList blks
blks'' <- removeOrphanAnchors blks'
diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs
index 978d6ff3a..aaa8f4ad0 100644
--- a/src/Text/Pandoc/Readers/Docx/Parse.hs
+++ b/src/Text/Pandoc/Readers/Docx/Parse.hs
@@ -33,7 +33,9 @@ module Text.Pandoc.Readers.Docx.Parse ( Docx(..)
, ParStyle
, CharStyle(cStyleData)
, Row(..)
+ , TblHeader(..)
, Cell(..)
+ , VMerge(..)
, TrackedChange(..)
, ChangeType(..)
, ChangeInfo(..)
@@ -50,6 +52,7 @@ module Text.Pandoc.Readers.Docx.Parse ( Docx(..)
, pHeading
, constructBogusParStyleData
, leftBiasedMergeRunStyle
+ , rowsToRowspans
) where
import Text.Pandoc.Readers.Docx.Parse.Styles
import Codec.Archive.Zip
@@ -225,6 +228,7 @@ defaultParagraphStyle = ParagraphStyle { pStyle = []
data BodyPart = Paragraph ParagraphStyle [ParPart]
| ListItem ParagraphStyle T.Text T.Text (Maybe Level) [ParPart]
| Tbl T.Text TblGrid TblLook [Row]
+ | TblCaption ParagraphStyle [ParPart]
| OMathPara [Exp]
deriving Show
@@ -236,12 +240,61 @@ newtype TblLook = TblLook {firstRowFormatting::Bool}
defaultTblLook :: TblLook
defaultTblLook = TblLook{firstRowFormatting = False}
-newtype Row = Row [Cell]
- deriving Show
+data Row = Row TblHeader [Cell] deriving Show
+
+data TblHeader = HasTblHeader | NoTblHeader deriving (Show, Eq)
-newtype Cell = Cell [BodyPart]
+data Cell = Cell GridSpan VMerge [BodyPart]
deriving Show
+type GridSpan = Integer
+
+data VMerge = Continue
+ -- ^ This cell should be merged with the one above it
+ | Restart
+ -- ^ This cell should not be merged with the one above it
+ deriving (Show, Eq)
+
+rowsToRowspans :: [Row] -> [[(Int, Cell)]]
+rowsToRowspans rows = let
+ removeMergedCells = fmap (filter (\(_, Cell _ vmerge _) -> vmerge == Restart))
+ in removeMergedCells (foldr f [] rows)
+ where
+ f :: Row -> [[(Int, Cell)]] -> [[(Int, Cell)]]
+ f (Row _ cells) acc = let
+ spans = g cells Nothing (listToMaybe acc)
+ in spans : acc
+
+ g ::
+ -- | The current row
+ [Cell] ->
+ -- | Number of columns left below
+ Maybe Integer ->
+ -- | (rowspan so far, cell) for the row below this one
+ Maybe [(Int, Cell)] ->
+ -- | (rowspan so far, cell) for this row
+ [(Int, Cell)]
+ g cells _ Nothing = zip (repeat 1) cells
+ g cells columnsLeftBelow (Just rowBelow) =
+ case cells of
+ [] -> []
+ thisCell@(Cell thisGridSpan _ _) : restOfRow -> case rowBelow of
+ [] -> zip (repeat 1) cells
+ (spanSoFarBelow, Cell gridSpanBelow vmerge _) : _ ->
+ let spanSoFar = case vmerge of
+ Restart -> 1
+ Continue -> 1 + spanSoFarBelow
+ columnsToDrop = thisGridSpan + (gridSpanBelow - fromMaybe gridSpanBelow columnsLeftBelow)
+ (newColumnsLeftBelow, restOfRowBelow) = dropColumns columnsToDrop rowBelow
+ in (spanSoFar, thisCell) : g restOfRow (Just newColumnsLeftBelow) (Just restOfRowBelow)
+
+ dropColumns :: Integer -> [(a, Cell)] -> (Integer, [(a, Cell)])
+ dropColumns n [] = (n, [])
+ dropColumns n cells@((_, Cell gridSpan _ _) : otherCells) =
+ if n < gridSpan
+ then (gridSpan - n, cells)
+ else dropColumns (n - gridSpan) otherCells
+
leftBiasedMergeRunStyle :: RunStyle -> RunStyle -> RunStyle
leftBiasedMergeRunStyle a b = RunStyle
{ isBold = isBold a <|> isBold b
@@ -587,14 +640,31 @@ elemToRow ns element | isElem ns "w" "tr" element =
do
let cellElems = findChildrenByName ns "w" "tc" element
cells <- mapD (elemToCell ns) cellElems
- return $ Row cells
+ let hasTblHeader = maybe NoTblHeader (const HasTblHeader)
+ (findChildByName ns "w" "trPr" element
+ >>= findChildByName ns "w" "tblHeader")
+ return $ Row hasTblHeader cells
elemToRow _ _ = throwError WrongElem
elemToCell :: NameSpaces -> Element -> D Cell
elemToCell ns element | isElem ns "w" "tc" element =
do
+ let properties = findChildByName ns "w" "tcPr" element
+ let gridSpan = properties
+ >>= findChildByName ns "w" "gridSpan"
+ >>= findAttrByName ns "w" "val"
+ >>= stringToInteger
+ let vMerge = case properties >>= findChildByName ns "w" "vMerge" of
+ Nothing -> Restart
+ Just e ->
+ fromMaybe Continue $ do
+ s <- findAttrByName ns "w" "val" e
+ case s of
+ "continue" -> Just Continue
+ "restart" -> Just Restart
+ _ -> Nothing
cellContents <- mapD (elemToBodyPart ns) (elChildren element)
- return $ Cell cellContents
+ return $ Cell (fromMaybe 1 gridSpan) vMerge cellContents
elemToCell _ _ = throwError WrongElem
elemToParIndentation :: NameSpaces -> Element -> Maybe ParIndentation
@@ -626,10 +696,9 @@ pNumInfo = getParStyleField numInfo . pStyle
elemToBodyPart :: NameSpaces -> Element -> D BodyPart
elemToBodyPart ns element
| isElem ns "w" "p" element
- , (c:_) <- findChildrenByName ns "m" "oMathPara" element =
- do
- expsLst <- eitherToD $ readOMML $ showElement c
- return $ OMathPara expsLst
+ , (c:_) <- findChildrenByName ns "m" "oMathPara" element = do
+ expsLst <- eitherToD $ readOMML $ showElement c
+ return $ OMathPara expsLst
elemToBodyPart ns element
| isElem ns "w" "p" element
, Just (numId, lvl) <- getNumInfo ns element = do
@@ -647,13 +716,31 @@ elemToBodyPart ns element
Nothing | Just (numId, lvl) <- pNumInfo parstyle -> do
levelInfo <- lookupLevel numId lvl <$> asks envNumbering
return $ ListItem parstyle numId lvl levelInfo parparts
- _ -> return $ Paragraph parstyle parparts
+ _ -> let
+ hasCaptionStyle = elem "Caption" (pStyleId <$> pStyle parstyle)
+
+ hasSimpleTableField = fromMaybe False $ do
+ fldSimple <- findChildByName ns "w" "fldSimple" element
+ instr <- findAttrByName ns "w" "instr" fldSimple
+ pure ("Table" `elem` T.words instr)
+
+ hasComplexTableField = fromMaybe False $ do
+ instrText <- findElementByName ns "w" "instrText" element
+ pure ("Table" `elem` T.words (strContent instrText))
+
+ in if hasCaptionStyle && (hasSimpleTableField || hasComplexTableField)
+ then return $ TblCaption parstyle parparts
+ else return $ Paragraph parstyle parparts
+
elemToBodyPart ns element
| isElem ns "w" "tbl" element = do
- let caption' = findChildByName ns "w" "tblPr" element
+ let tblProperties = findChildByName ns "w" "tblPr" element
+ caption = fromMaybe "" $ tblProperties
>>= findChildByName ns "w" "tblCaption"
>>= findAttrByName ns "w" "val"
- caption = fromMaybe "" caption'
+ description = fromMaybe "" $ tblProperties
+ >>= findChildByName ns "w" "tblDescription"
+ >>= findAttrByName ns "w" "val"
grid' = case findChildByName ns "w" "tblGrid" element of
Just g -> elemToTblGrid ns g
Nothing -> return []
@@ -666,7 +753,7 @@ elemToBodyPart ns element
grid <- grid'
tblLook <- tblLook'
rows <- mapD (elemToRow ns) (elChildren element)
- return $ Tbl caption grid tblLook rows
+ return $ Tbl (caption <> description) grid tblLook rows
elemToBodyPart _ _ = throwError WrongElem
lookupRelationship :: DocumentLocation -> RelId -> [Relationship] -> Maybe Target
diff --git a/src/Text/Pandoc/Readers/Docx/Util.hs b/src/Text/Pandoc/Readers/Docx/Util.hs
index ac331cba6..970697a2d 100644
--- a/src/Text/Pandoc/Readers/Docx/Util.hs
+++ b/src/Text/Pandoc/Readers/Docx/Util.hs
@@ -19,6 +19,7 @@ module Text.Pandoc.Readers.Docx.Util (
, elemToNameSpaces
, findChildByName
, findChildrenByName
+ , findElementByName
, findAttrByName
) where
@@ -56,6 +57,12 @@ findChildrenByName ns pref name el =
let ns' = ns <> elemToNameSpaces el
in findChildren (elemName ns' pref name) el
+-- | Like 'findChildrenByName', but searches descendants.
+findElementByName :: NameSpaces -> Text -> Text -> Element -> Maybe Element
+findElementByName ns pref name el =
+ let ns' = ns <> elemToNameSpaces el
+ in findElement (elemName ns' pref name) el
+
findAttrByName :: NameSpaces -> Text -> Text -> Element -> Maybe Text
findAttrByName ns pref name el =
let ns' = ns <> elemToNameSpaces el
diff --git a/test/Tests/Readers/Docx.hs b/test/Tests/Readers/Docx.hs
index 939ff9939..220c7d9c5 100644
--- a/test/Tests/Readers/Docx.hs
+++ b/test/Tests/Readers/Docx.hs
@@ -318,14 +318,30 @@ tests = [ testGroup "document"
"docx/table_with_list_cell.docx"
"docx/table_with_list_cell.native"
, testCompare
+ "a table with a header which contains rowspans greater than 1"
+ "docx/table_header_rowspan.docx"
+ "docx/table_header_rowspan.native"
+ , testCompare
"tables with one row"
"docx/table_one_row.docx"
"docx/table_one_row.native"
, testCompare
+ "tables with just one row, which is a header"
+ "docx/table_one_header_row.docx"
+ "docx/table_one_header_row.native"
+ , testCompare
"tables with variable width"
"docx/table_variable_width.docx"
"docx/table_variable_width.native"
, testCompare
+ "tables with captions which contain a Table field"
+ "docx/table_captions_with_field.docx"
+ "docx/table_captions_with_field.native"
+ , testCompare
+ "tables with captions which don't contain a Table field"
+ "docx/table_captions_no_field.docx"
+ "docx/table_captions_no_field.native"
+ , testCompare
"code block"
"docx/codeblock.docx"
"docx/codeblock.native"
diff --git a/test/docx/sdt_elements.native b/test/docx/sdt_elements.native
index a072c0d39..d2aa00994 100644
--- a/test/docx/sdt_elements.native
+++ b/test/docx/sdt_elements.native
@@ -4,17 +4,16 @@
,(AlignDefault,ColWidth 0.22069570301081556)
,(AlignDefault,ColWidth 0.5586085939783689)]
(TableHead ("",[],[])
- [])
- [(TableBody ("",[],[]) (RowHeadColumns 0)
- []
- [Row ("",[],[])
+ [Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Strong [Str "col1Header"]]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Strong [Str "col2Header"]]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
- [Plain [Strong [Str "col3Header"]]]]
- ,Row ("",[],[])
+ [Plain [Strong [Str "col3Header"]]]]])
+ [(TableBody ("",[],[]) (RowHeadColumns 0)
+ []
+ [Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "col1",Space,Str "content"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
@@ -22,4 +21,4 @@
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "col3",Space,Str "content"]]]])]
(TableFoot ("",[],[])
- [])] \ No newline at end of file
+ [])]
diff --git a/test/docx/table_captions_no_field.docx b/test/docx/table_captions_no_field.docx
new file mode 100644
index 000000000..1687d32a2
--- /dev/null
+++ b/test/docx/table_captions_no_field.docx
Binary files differ
diff --git a/test/docx/table_captions_no_field.native b/test/docx/table_captions_no_field.native
new file mode 100644
index 000000000..b8f54d541
--- /dev/null
+++ b/test/docx/table_captions_no_field.native
@@ -0,0 +1,34 @@
+[Para [Str "See",Space,Str "Table",Space,Str "5.1."]
+,Para [Str "Table",Space,Str "5.1"]
+,Table ("",[],[]) (Caption Nothing
+ [])
+ [(AlignDefault,ColWidth 0.7605739372523825)
+ ,(AlignDefault,ColWidth 0.11971303137380876)
+ ,(AlignDefault,ColWidth 0.11971303137380876)]
+ (TableHead ("",[],[])
+[Row ("",[],[])
+ [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ []
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "Count"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "%"]]]])
+ [(TableBody ("",[],[]) (RowHeadColumns 0)
+ []
+ [Row ("",[],[])
+ [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "First",Space,Str "option"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "242"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "45"]]]
+,Row ("",[],[])
+ [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "Second",Space,Str "option"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "99"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "18"]]]])]
+ (TableFoot ("",[],[])
+ [])
+,Header 2 ("section", [], []) []]
diff --git a/test/docx/table_captions_with_field.docx b/test/docx/table_captions_with_field.docx
new file mode 100644
index 000000000..db6de3088
--- /dev/null
+++ b/test/docx/table_captions_with_field.docx
Binary files differ
diff --git a/test/docx/table_captions_with_field.native b/test/docx/table_captions_with_field.native
new file mode 100644
index 000000000..deb8afc6b
--- /dev/null
+++ b/test/docx/table_captions_with_field.native
@@ -0,0 +1,54 @@
+[Para [Str "See",Space,Str "Table",Space,Str "1."]
+,Para []
+,Table ("",[],[]) (Caption Nothing
+ [Para [Str "Table",Space,Str "1"]])
+ [(AlignDefault,ColWidth 0.7605739372523825)
+ ,(AlignDefault,ColWidth 0.11971303137380876)
+ ,(AlignDefault,ColWidth 0.11971303137380876)]
+ (TableHead ("",[],[])
+[Row ("",[],[])
+ [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ []
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "Count"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "%"]]]])
+ [(TableBody ("",[],[]) (RowHeadColumns 0)
+ []
+ [Row ("",[],[])
+ [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "First",Space,Str "option"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "242"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "45"]]]
+,Row ("",[],[])
+ [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "Second",Space,Str "option"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "99"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "18"]]]])]
+ (TableFoot ("",[],[])
+ [])
+,Header 2 ("section", [], []) []
+,Table ("",[],[]) (Caption Nothing
+ [Para [Str "Table",Space,Str "2"]])
+ [(AlignDefault,ColWidth 0.3332963620230701)
+ ,(AlignDefault,ColWidth 0.3332963620230701)
+ ,(AlignDefault,ColWidth 0.3334072759538598)]
+ (TableHead ("",[],[])
+ [Row ("",[],[])
+ [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "One"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "Two"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "Three"]]]])
+ [(TableBody ("",[],[]) (RowHeadColumns 0)
+ []
+ [])]
+ (TableFoot ("",[],[])
+ [])
+,Para []
+,Para [Str "See",Space,Str "Table",Space,Str "2."]]
diff --git a/test/docx/table_header_rowspan.docx b/test/docx/table_header_rowspan.docx
new file mode 100644
index 000000000..1cc32a105
--- /dev/null
+++ b/test/docx/table_header_rowspan.docx
Binary files differ
diff --git a/test/docx/table_header_rowspan.native b/test/docx/table_header_rowspan.native
new file mode 100644
index 000000000..d951f29e4
--- /dev/null
+++ b/test/docx/table_header_rowspan.native
@@ -0,0 +1,189 @@
+[Table ("",[],[]) (Caption Nothing
+ [])
+ [(AlignDefault,ColWidth 0.30701754385964913)
+ ,(AlignDefault,ColWidth 0.1364522417153996)
+ ,(AlignDefault,ColWidth 0.10009746588693957)
+ ,(AlignDefault,ColWidth 9.707602339181287e-2)
+ ,(AlignDefault,ColWidth 7.719298245614035e-2)
+ ,(AlignDefault,ColWidth 7.085769980506823e-2)
+ ,(AlignDefault,ColWidth 7.09551656920078e-2)
+ ,(AlignDefault,ColWidth 0.14035087719298245)]
+ (TableHead ("",[],[])
+[Row ("",[],[])
+ [Cell ("",[],[]) AlignDefault (RowSpan 2) (ColSpan 1)
+ [Plain [Str "A"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 2) (ColSpan 1)
+ [Plain [Strong [Str "B"]]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 2) (ColSpan 1)
+ [Plain [Strong [Str "C"]]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 2) (ColSpan 1)
+ [Plain [Strong [Str "D"]]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 3)
+ [Plain [Str "E"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 2) (ColSpan 1)
+ [Plain [Str "F"]]]
+,Row ("",[],[])
+ [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Strong [Str "G"]]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Strong [Str "H"]]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Strong [Str "I"]]]]])
+ [(TableBody ("",[],[]) (RowHeadColumns 0)
+ []
+ [Row ("",[],[])
+ [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "1"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "2"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "3"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "4"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "5"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "6"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "7"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "8"]]]
+ ,Row ("",[],[])
+ [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "1"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "2"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "3"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "4"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "5"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "6"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "7"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "8"]]]
+ ,Row ("",[],[])
+ [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "1"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "2"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "3"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "4"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "5"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "6"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "7"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "8"]]]
+ ,Row ("",[],[])
+ [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "1"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "2"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "3"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "4"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "5"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "6"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "7"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "8"]]]
+ ,Row ("",[],[])
+ [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "1"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "2"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "3"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "4"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "5"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "6"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "7"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "8"]]]
+ ,Row ("",[],[])
+ [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "1"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "2"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "3"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "4"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "5"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "6"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "7"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "8"]]]
+ ,Row ("",[],[])
+ [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "1"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "2"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "3"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "4"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "5"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "6"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "7"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "8"]]]
+ ,Row ("",[],[])
+ [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "1"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "2"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "3"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "4"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "5"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "6"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "7"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "8"]]]
+ ,Row ("",[],[])
+ [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "1"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "2"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "3"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "4"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "5"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "6"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "7"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "8"]]]
+ ])]
+ (TableFoot ("",[],[])
+ [])]
diff --git a/test/docx/table_one_header_row.docx b/test/docx/table_one_header_row.docx
new file mode 100644
index 000000000..db715dda8
--- /dev/null
+++ b/test/docx/table_one_header_row.docx
Binary files differ
diff --git a/test/docx/table_one_header_row.native b/test/docx/table_one_header_row.native
new file mode 100644
index 000000000..4aae830ac
--- /dev/null
+++ b/test/docx/table_one_header_row.native
@@ -0,0 +1,18 @@
+[Table ("",[],[]) (Caption Nothing
+ [])
+ [(AlignDefault,ColWidth 0.33302433371958284)
+ ,(AlignDefault,ColWidth 0.3332560834298957)
+ ,(AlignDefault,ColWidth 0.33371958285052145)]
+ (TableHead ("",[],[])
+ [Row ("",[],[])
+ [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "One"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "Row"]]
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Plain [Str "Table"]]]])
+ [(TableBody ("",[],[]) (RowHeadColumns 0)
+ []
+ [])]
+ (TableFoot ("",[],[])
+ [])]
diff --git a/test/docx/table_one_row.docx b/test/docx/table_one_row.docx
index f7e0ebe43..d05a856b5 100644
--- a/test/docx/table_one_row.docx
+++ b/test/docx/table_one_row.docx
Binary files differ
diff --git a/test/docx/table_variable_width.native b/test/docx/table_variable_width.native
index 43ac40cca..ff1cc0dc4 100644
--- a/test/docx/table_variable_width.native
+++ b/test/docx/table_variable_width.native
@@ -4,7 +4,8 @@
,(AlignDefault,ColWidth 1.9882415820416888e-2)
,(AlignDefault,ColWidth 0.22202030999465527)
,(AlignDefault,ColWidth 0.4761090326028862)
- ,(AlignDefault,ColWidth 1.0689470871191876e-4)]
+ ,(AlignDefault,ColWidth 1.0689470871191876e-4)
+ ,(AlignDefault,ColWidth 0.26178514163548905)]
(TableHead ("",[],[])
[Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
@@ -13,33 +14,27 @@
[]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "h3"]]
- ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 2)
[Plain [Str "h4"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "h5"]]]])
[(TableBody ("",[],[]) (RowHeadColumns 0)
[]
[Row ("",[],[])
- [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 3)
[Plain [Str "c11"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[]
- ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
- []
- ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
- []
- ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 2)
[]]
,Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[]
- ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 2)
[Plain [Str "c22"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "c23"]]
- ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
- []
- ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+ ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 2)
[]]])]
(TableFoot ("",[],[])
[])]