@@ -307,13 +307,9 @@ gridTable opts blocksToDoc colspecs' thead' tbodies' tfoot' = do
307307 let getBodyCells (Ann. BodyRow _ _ rhcells cells) = rhcells ++ cells
308308 let getBody (Ann. TableBody _ _ hs xs) = map getHeadCells hs <> map getBodyCells xs
309309 bodyCells <- mapM (renderRows . getBody) tbodies
310- let rows = setTopBorder SingleLine headCells ++
311- (setTopBorder (if null headCells then SingleLine else DoubleLine )
312- . setBottomBorder SingleLine ) (mconcat bodyCells) ++
313- (if null footCells
314- then mempty
315- else setTopBorder DoubleLine . setBottomBorder DoubleLine $
316- footCells)
310+ let rows = (setTopBorder SingleLine . setBottomBorder DoubleLine ) headCells ++
311+ (setTopBorder SingleLine . setBottomBorder SingleLine ) (mconcat bodyCells) ++
312+ (setTopBorder DoubleLine . setBottomBorder DoubleLine ) footCells
317313 pure $ gridRows $ redoWidths opts colspecs rows
318314
319315-- Returns (current widths, full widths, min widths)
@@ -367,6 +363,7 @@ makeDummy :: RenderedCell Text -> RenderedCell Text
367363makeDummy c =
368364 RenderedCell { cellColNum = cellColNum c,
369365 cellColSpan = cellColSpan c,
366+ cellColSpecs = cellColSpecs c,
370367 cellAlign = AlignDefault ,
371368 cellRowSpan = cellRowSpan c - 1 ,
372369 cellWidth = cellWidth c,
@@ -437,8 +434,8 @@ gridRows (x:xs) =
437434
438435 rowAndBottom thisRow nextRow =
439436 let isLastRow = null nextRow
440- border1 = render Nothing (formatBorder cellBottomBorder False thisRow)
441- border2 = render Nothing (formatBorder cellTopBorder True nextRow)
437+ border1 = render Nothing (formatBorder cellBottomBorder True thisRow)
438+ border2 = render Nothing (formatBorder cellTopBorder False nextRow)
442439 go ' +' _ = ' +'
443440 go _ ' +' = ' +'
444441 go ' :' _ = ' :'
@@ -491,6 +488,7 @@ data LineStyle = NoLine | SingleLine | DoubleLine
491488data RenderedCell a =
492489 RenderedCell { cellColNum :: Int
493490 , cellColSpan :: Int
491+ , cellColSpecs :: NonEmpty ColSpec
494492 , cellAlign :: Alignment
495493 , cellRowSpan :: Int
496494 , cellWidth :: Int
@@ -523,6 +521,7 @@ gridRow opts blocksToDoc = mapM renderCell
523521 rendered <- renderer blocks
524522 pure $ RenderedCell { cellColNum = colnum,
525523 cellColSpan = length cellcolspecs,
524+ cellColSpecs = cellcolspecs,
526525 cellAlign = align,
527526 cellRowSpan = rowspan,
528527 cellWidth = width,
0 commit comments