Remove the onlySimpleCellBodies function from Shared
This commit is contained in:
parent
7254a2ae0b
commit
f8ce38975b
5 changed files with 7 additions and 18 deletions
|
@ -61,7 +61,7 @@ import Text.Pandoc.Options (
|
|||
import Text.Pandoc.Parsing hiding ((<|>))
|
||||
import Text.Pandoc.Shared (addMetaField, blocksToInlines', crFilter, escapeURI,
|
||||
extractSpaces, htmlSpanLikeElements, elemText, splitTextBy,
|
||||
onlySimpleCellBodies, safeRead, underlineSpan, tshow)
|
||||
onlySimpleTableCells, safeRead, underlineSpan, tshow)
|
||||
import Text.Pandoc.Walk
|
||||
import Text.Parsec.Error
|
||||
import Text.TeXMath (readMathML, writeTeX)
|
||||
|
@ -499,7 +499,7 @@ pTable = try $ do
|
|||
let rows''' = map (map snd) rows''
|
||||
-- fail on empty table
|
||||
guard $ not $ null head' && null rows'''
|
||||
let isSimple = onlySimpleCellBodies $ fmap B.toList <$> head':rows'''
|
||||
let isSimple = onlySimpleTableCells $ fmap B.toList <$> head':rows'''
|
||||
let cols = if null head'
|
||||
then maximum (map length rows''')
|
||||
else length head'
|
||||
|
|
|
@ -67,7 +67,6 @@ module Text.Pandoc.Shared (
|
|||
headerShift,
|
||||
stripEmptyParagraphs,
|
||||
onlySimpleTableCells,
|
||||
onlySimpleCellBodies,
|
||||
isTightList,
|
||||
taskListItemFromAscii,
|
||||
taskListItemToAscii,
|
||||
|
@ -669,18 +668,8 @@ stripEmptyParagraphs = walk go
|
|||
|
||||
-- | Detect if table rows contain only cells consisting of a single
|
||||
-- paragraph that has no @LineBreak@.
|
||||
|
||||
-- TODO: should this become aware of cell dimensions?
|
||||
onlySimpleTableCells :: [Row] -> Bool
|
||||
onlySimpleTableCells = onlySimpleCellBodies . map unRow
|
||||
where
|
||||
unRow (Row _ body) = map unCell body
|
||||
unCell (Cell _ _ _ _ body) = body
|
||||
|
||||
-- | Detect if unwrapped table rows contain only cells consisting of a
|
||||
-- single paragraph that has no @LineBreak@.
|
||||
onlySimpleCellBodies :: [[[Block]]] -> Bool
|
||||
onlySimpleCellBodies = all isSimpleCell . concat
|
||||
onlySimpleTableCells :: [[[Block]]] -> Bool
|
||||
onlySimpleTableCells = all isSimpleCell . concat
|
||||
where
|
||||
isSimpleCell [Plain ils] = not (hasLineBreak ils)
|
||||
isSimpleCell [Para ils ] = not (hasLineBreak ils)
|
||||
|
|
|
@ -156,7 +156,7 @@ blockToNodes opts (DefinitionList items) ns =
|
|||
Para term : concat xs
|
||||
blockToNodes opts t@(Table _ blkCapt specs _ thead tbody tfoot) ns =
|
||||
let (capt, aligns, _widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
in if isEnabled Ext_pipe_tables opts && onlySimpleTableCells (thead <> tbody <> tfoot)
|
||||
in if isEnabled Ext_pipe_tables opts && onlySimpleTableCells (headers : rows)
|
||||
then do
|
||||
-- We construct a table manually as a CUSTOM_BLOCK, for
|
||||
-- two reasons: (1) cmark-gfm currently doesn't support
|
||||
|
|
|
@ -582,7 +582,7 @@ blockToMarkdown' opts t@(Table _ blkCapt specs _ thead tbody tfoot) = do
|
|||
let caption'' = if null caption || not (isEnabled Ext_table_captions opts)
|
||||
then blankline
|
||||
else blankline $$ (": " <> caption') $$ blankline
|
||||
let hasSimpleCells = onlySimpleTableCells $ thead <> tbody <> tfoot
|
||||
let hasSimpleCells = onlySimpleTableCells $ headers : rows
|
||||
let isSimple = hasSimpleCells && all (==0) widths
|
||||
let isPlainBlock (Plain _) = True
|
||||
isPlainBlock _ = False
|
||||
|
|
|
@ -270,7 +270,7 @@ blockToMuse (Table _ blkCapt specs _ thead tbody tfoot) =
|
|||
blocksToDoc opts blocks =
|
||||
local (\env -> env { envOptions = opts }) $ blockListToMuse blocks
|
||||
numcols = maximum (length aligns : length widths : map length (headers:rows))
|
||||
isSimple = onlySimpleTableCells (thead <> tbody <> tfoot) && all (== 0) widths
|
||||
isSimple = onlySimpleTableCells (headers : rows) && all (== 0) widths
|
||||
blockToMuse (Div _ bs) = flatBlockListToMuse bs
|
||||
blockToMuse Null = return empty
|
||||
|
||||
|
|
Loading…
Add table
Reference in a new issue