Use the new builders, modify readers to preserve empty headers
The Builder.simpleTable now only adds a row to the TableHead when the given header row is not null. This uncovered an inconsistency in the readers: some would unconditionally emit a header filled with empty cells, even if the header was not present. Now every reader has the conditional behaviour. Only the XWiki writer depended on the header row being always present; it now pads its head as necessary.
This commit is contained in:
parent
d368536a4e
commit
c7814f31e1
55 changed files with 375 additions and 572 deletions
|
@ -197,7 +197,7 @@ peekBlock idx = defineHowTo "get Block value" $ do
|
|||
Table nullAttr
|
||||
(Caption Nothing $ maybePlain capt)
|
||||
(zip aligns (map strictPos widths))
|
||||
(TableHead nullAttr [toRow headers])
|
||||
(TableHead nullAttr $ toHeaderRow headers)
|
||||
[TableBody nullAttr 0 [] (map toRow body)]
|
||||
(TableFoot nullAttr []))
|
||||
<$> elementContent
|
||||
|
@ -211,6 +211,7 @@ peekBlock idx = defineHowTo "get Block value" $ do
|
|||
maybePlain [] = []
|
||||
maybePlain x = [Plain x]
|
||||
toRow = Row nullAttr . map (\blk -> Cell nullAttr AlignDefault 1 1 blk)
|
||||
toHeaderRow l = if null l then [] else [toRow l]
|
||||
|
||||
-- | Push an inline element to the top of the lua stack.
|
||||
pushInline :: Inline -> Lua ()
|
||||
|
|
|
@ -925,13 +925,16 @@ tableWith :: (Stream s m Char, HasReaderOptions st, Monad mf)
|
|||
tableWith headerParser rowParser lineParser footerParser = try $ do
|
||||
(aligns, widths, heads, rows) <- tableWith' headerParser rowParser
|
||||
lineParser footerParser
|
||||
return $ B.table mempty (zip aligns (map fromWidth widths)) <$> heads <*> rows
|
||||
let th = TableHead nullAttr <$> heads
|
||||
tb = (:[]) . TableBody nullAttr 0 [] <$> rows
|
||||
tf = pure $ TableFoot nullAttr []
|
||||
return $ B.table B.emptyCaption (zip aligns (map fromWidth widths)) <$> th <*> tb <*> tf
|
||||
where
|
||||
fromWidth n
|
||||
| n > 0 = ColWidth n
|
||||
| otherwise = ColWidthDefault
|
||||
|
||||
type TableComponents mf = ([Alignment], [Double], mf [Blocks], mf [[Blocks]])
|
||||
type TableComponents mf = ([Alignment], [Double], mf [Row], mf [Row])
|
||||
|
||||
tableWith' :: (Stream s m Char, HasReaderOptions st, Monad mf)
|
||||
=> ParserT s st m (mf [Blocks], [Alignment], [Int])
|
||||
|
@ -947,7 +950,9 @@ tableWith' headerParser rowParser lineParser footerParser = try $ do
|
|||
let widths = if null indices
|
||||
then replicate (length aligns) 0.0
|
||||
else widthsFromIndices numColumns indices
|
||||
return (aligns, widths, heads, lines')
|
||||
let toRow = Row nullAttr . map B.simpleCell
|
||||
toHeaderRow l = if null l then [] else [toRow l]
|
||||
return (aligns, widths, toHeaderRow <$> heads, map toRow <$> lines')
|
||||
|
||||
-- Calculate relative widths of table columns, based on indices
|
||||
widthsFromIndices :: Int -- Number of columns on terminal
|
||||
|
|
|
@ -30,12 +30,18 @@ readCSV :: PandocMonad m
|
|||
-> m Pandoc
|
||||
readCSV _opts s =
|
||||
case parseCSV defaultCSVOptions (crFilter s) of
|
||||
Right (r:rs) -> return $ B.doc $ B.table capt (zip aligns widths) hdrs rows
|
||||
where capt = mempty
|
||||
Right (r:rs) -> return $ B.doc $ B.table capt
|
||||
(zip aligns widths)
|
||||
(TableHead nullAttr hdrs)
|
||||
[TableBody nullAttr 0 [] rows]
|
||||
(TableFoot nullAttr [])
|
||||
where capt = B.emptyCaption
|
||||
numcols = length r
|
||||
toplain = B.plain . B.text . T.strip
|
||||
hdrs = map toplain r
|
||||
rows = map (map toplain) rs
|
||||
toplain = B.simpleCell . B.plain . B.text . T.strip
|
||||
toRow = Row nullAttr . map toplain
|
||||
toHeaderRow l = if null l then [] else [toRow l]
|
||||
hdrs = toHeaderRow r
|
||||
rows = map toRow rs
|
||||
aligns = replicate numcols AlignDefault
|
||||
widths = replicate numcols ColWidthDefault
|
||||
Right [] -> return $ B.doc mempty
|
||||
|
|
|
@ -887,11 +887,13 @@ parseBlock (Elem e) =
|
|||
Just ws' -> let tot = sum ws'
|
||||
in ColWidth . (/ tot) <$> ws'
|
||||
Nothing -> replicate numrows ColWidthDefault
|
||||
let headrows' = if null headrows
|
||||
then replicate numrows mempty
|
||||
else headrows
|
||||
return $ table capt (zip aligns widths)
|
||||
headrows' bodyrows
|
||||
let toRow = Row nullAttr . map simpleCell
|
||||
toHeaderRow l = if null l then [] else [toRow l]
|
||||
return $ table (simpleCaption $ plain capt)
|
||||
(zip aligns widths)
|
||||
(TableHead nullAttr $ toHeaderRow headrows)
|
||||
[TableBody nullAttr 0 [] $ map toRow bodyrows]
|
||||
(TableFoot nullAttr [])
|
||||
isEntry x = named "entry" x || named "td" x || named "th" x
|
||||
parseRow = mapM (parseMixed plain . elContent) . filterChildren isEntry
|
||||
sect n = do isbook <- gets dbBook
|
||||
|
|
|
@ -72,7 +72,7 @@ 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
|
||||
|
@ -645,7 +645,7 @@ bodyPartToBlocks (ListItem pPr _ _ _ parparts) =
|
|||
bodyPartToBlocks (Tbl _ _ _ []) =
|
||||
return $ para mempty
|
||||
bodyPartToBlocks (Tbl cap _ look parts@(r:rs)) = do
|
||||
let cap' = text cap
|
||||
let cap' = simpleCaption $ plain $ text cap
|
||||
(hdr, rows) = case firstRowFormatting look of
|
||||
True | null rs -> (Nothing, [r])
|
||||
| otherwise -> (Just r, rs)
|
||||
|
@ -662,13 +662,16 @@ bodyPartToBlocks (Tbl cap _ look parts@(r:rs)) = do
|
|||
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
|
||||
|
@ -678,7 +681,11 @@ bodyPartToBlocks (Tbl cap _ look parts@(r:rs)) = do
|
|||
let alignments = replicate width AlignDefault
|
||||
widths = replicate width ColWidthDefault
|
||||
|
||||
return $ table cap' (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)
|
||||
|
||||
|
|
|
@ -471,7 +471,13 @@ table = do
|
|||
then (head rows, tail rows)
|
||||
else ([], rows)
|
||||
let attrs = (AlignDefault, ColWidthDefault) <$ transpose rows
|
||||
pure $ B.table mempty attrs headerRow body
|
||||
let toRow = Row nullAttr . map B.simpleCell
|
||||
toHeaderRow l = if null l then [] else [toRow l]
|
||||
pure $ B.table B.emptyCaption
|
||||
attrs
|
||||
(TableHead nullAttr $ toHeaderRow headerRow)
|
||||
[TableBody nullAttr 0 [] $ map toRow body]
|
||||
(TableFoot nullAttr [])
|
||||
|
||||
tableRows :: PandocMonad m => DWParser m [[B.Blocks]]
|
||||
tableRows = many1 tableRow
|
||||
|
|
|
@ -516,7 +516,13 @@ pTable = try $ do
|
|||
then replicate cols ColWidthDefault
|
||||
else replicate cols (ColWidth (1.0 / fromIntegral cols))
|
||||
else widths'
|
||||
return $ B.table caption (zip aligns widths) head' rows
|
||||
let toRow = Row nullAttr . map B.simpleCell
|
||||
toHeaderRow l = if null l then [] else [toRow l]
|
||||
return $ B.table (B.simpleCaption $ B.plain caption)
|
||||
(zip aligns widths)
|
||||
(TableHead nullAttr $ toHeaderRow head')
|
||||
[TableBody nullAttr 0 [] $ map toRow rows]
|
||||
(TableFoot nullAttr [])
|
||||
|
||||
pCol :: PandocMonad m => TagParser m ColWidth
|
||||
pCol = try $ do
|
||||
|
|
|
@ -85,6 +85,8 @@ docHToBlocks d' =
|
|||
, tableBodyRows = bodyRows
|
||||
}
|
||||
-> let toCells = map (docHToBlocks . tableCellContents) . tableRowCells
|
||||
toRow = Row nullAttr . map B.simpleCell
|
||||
toHeaderRow l = if null l then [] else [toRow l]
|
||||
(header, body) =
|
||||
if null headerRows
|
||||
then ([], map toCells bodyRows)
|
||||
|
@ -92,7 +94,11 @@ docHToBlocks d' =
|
|||
map toCells (tail headerRows ++ bodyRows))
|
||||
colspecs = replicate (maximum (map length body))
|
||||
(AlignDefault, ColWidthDefault)
|
||||
in B.table mempty colspecs header body
|
||||
in B.table B.emptyCaption
|
||||
colspecs
|
||||
(TableHead nullAttr $ toHeaderRow header)
|
||||
[TableBody nullAttr 0 [] $ map toRow body]
|
||||
(TableFoot nullAttr [])
|
||||
|
||||
where inlineFallback = B.plain $ docHToInlines False d'
|
||||
consolidatePlains = B.fromList . consolidatePlains' . B.toList
|
||||
|
|
|
@ -280,11 +280,13 @@ parseBlock (Elem e) =
|
|||
Just ws' -> let tot = sum ws'
|
||||
in ColWidth . (/ tot) <$> ws'
|
||||
Nothing -> replicate numrows ColWidthDefault
|
||||
let headrows' = if null headrows
|
||||
then replicate numrows mempty
|
||||
else headrows
|
||||
return $ table capt (zip aligns widths)
|
||||
headrows' bodyrows
|
||||
let toRow = Row nullAttr . map simpleCell
|
||||
toHeaderRow l = if null l then [] else [toRow l]
|
||||
return $ table (simpleCaption $ plain capt)
|
||||
(zip aligns widths)
|
||||
(TableHead nullAttr $ toHeaderRow headrows)
|
||||
[TableBody nullAttr 0 [] $ map toRow bodyrows]
|
||||
(TableFoot nullAttr [])
|
||||
isEntry x = named "entry" x || named "td" x || named "th" x
|
||||
parseRow = mapM (parseMixed plain . elContent) . filterChildren isEntry
|
||||
sect n = do isbook <- gets jatsBook
|
||||
|
|
|
@ -16,7 +16,7 @@ import Data.Text (Text, append, pack, singleton, unpack)
|
|||
import Text.HTML.TagSoup.Entity (lookupEntity)
|
||||
import Text.Jira.Parser (parse)
|
||||
import Text.Pandoc.Class.PandocMonad (PandocMonad (..))
|
||||
import Text.Pandoc.Builder
|
||||
import Text.Pandoc.Builder hiding (cell)
|
||||
import Text.Pandoc.Error (PandocError (PandocParseError))
|
||||
import Text.Pandoc.Options (ReaderOptions)
|
||||
import Text.Pandoc.Shared (stringify)
|
||||
|
|
|
@ -2372,7 +2372,6 @@ simpTable envname hasWidthParameter = try $ do
|
|||
skipopts
|
||||
colspecs <- parseAligns
|
||||
let (aligns, widths, prefsufs) = unzip3 colspecs
|
||||
let cols = length colspecs
|
||||
optional $ controlSeq "caption" *> setCaption
|
||||
spaces
|
||||
optional label
|
||||
|
@ -2393,11 +2392,14 @@ simpTable envname hasWidthParameter = try $ do
|
|||
spaces
|
||||
optional lbreak
|
||||
spaces
|
||||
let header'' = if null header'
|
||||
then replicate cols mempty
|
||||
else header'
|
||||
lookAhead $ controlSeq "end" -- make sure we're at end
|
||||
return $ table mempty (zip aligns widths) header'' rows
|
||||
let toRow = Row nullAttr . map simpleCell
|
||||
toHeaderRow l = if null l then [] else [toRow l]
|
||||
return $ table emptyCaption
|
||||
(zip aligns widths)
|
||||
(TableHead nullAttr $ toHeaderRow header')
|
||||
[TableBody nullAttr 0 [] $ map toRow rows]
|
||||
(TableFoot nullAttr [])
|
||||
|
||||
addTableCaption :: PandocMonad m => Blocks -> LP m Blocks
|
||||
addTableCaption = walkM go
|
||||
|
|
|
@ -109,8 +109,10 @@ parseTable = do
|
|||
let widths = if isPlainTable
|
||||
then repeat ColWidthDefault
|
||||
else repeat $ ColWidth (1.0 / fromIntegral (length alignments))
|
||||
return $ B.table mempty (zip alignments widths)
|
||||
headerRow bodyRows) <|> fallback pos
|
||||
return $ B.table B.emptyCaption (zip alignments widths)
|
||||
(TableHead nullAttr $ toHeaderRow headerRow)
|
||||
[TableBody nullAttr 0 [] $ map toRow bodyRows]
|
||||
(TableFoot nullAttr [])) <|> fallback pos
|
||||
[] -> fallback pos
|
||||
|
||||
where
|
||||
|
@ -159,6 +161,9 @@ parseTable = do
|
|||
'r' -> Just AlignRight
|
||||
_ -> Nothing
|
||||
|
||||
toRow = Row nullAttr . map simpleCell
|
||||
toHeaderRow l = if null l then [] else [toRow l]
|
||||
|
||||
parseNewParagraph :: PandocMonad m => ManParser m Blocks
|
||||
parseNewParagraph = do
|
||||
mmacro "P" <|> mmacro "PP" <|> mmacro "LP" <|> memptyLine
|
||||
|
|
|
@ -32,7 +32,7 @@ import Text.HTML.TagSoup
|
|||
import Text.Pandoc.Builder (Blocks, Inlines)
|
||||
import qualified Text.Pandoc.Builder as B
|
||||
import Text.Pandoc.Class.PandocMonad (PandocMonad (..), report)
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Definition as Pandoc
|
||||
import Text.Pandoc.Emoji (emojiToInline)
|
||||
import Text.Pandoc.Error
|
||||
import Text.Pandoc.Logging
|
||||
|
@ -1163,7 +1163,7 @@ simpleTableHeader headless = try $ do
|
|||
else return rawContent
|
||||
let aligns = zipWith alignType (map (: []) rawHeads) lengths
|
||||
let rawHeads' = if headless
|
||||
then replicate (length dashes) ""
|
||||
then []
|
||||
else rawHeads
|
||||
heads <- fmap sequence
|
||||
$
|
||||
|
@ -1235,7 +1235,7 @@ tableCaption = try $ do
|
|||
-- Parse a simple table with '---' header and one line per row.
|
||||
simpleTable :: PandocMonad m
|
||||
=> Bool -- ^ Headerless table
|
||||
-> MarkdownParser m ([Alignment], [Double], F [Blocks], F [[Blocks]])
|
||||
-> MarkdownParser m ([Alignment], [Double], F [Pandoc.Row], F [Pandoc.Row])
|
||||
simpleTable headless = do
|
||||
(aligns, _widths, heads', lines') <-
|
||||
tableWith (simpleTableHeader headless) tableLine
|
||||
|
@ -1250,7 +1250,7 @@ simpleTable headless = do
|
|||
-- ending with a footer (dashed line followed by blank line).
|
||||
multilineTable :: PandocMonad m
|
||||
=> Bool -- ^ Headerless table
|
||||
-> MarkdownParser m ([Alignment], [Double], F [Blocks], F [[Blocks]])
|
||||
-> MarkdownParser m ([Alignment], [Double], F [Pandoc.Row], F [Pandoc.Row])
|
||||
multilineTable headless =
|
||||
tableWith (multilineTableHeader headless) multilineRow blanklines tableFooter
|
||||
|
||||
|
@ -1281,7 +1281,7 @@ multilineTableHeader headless = try $ do
|
|||
rawContent
|
||||
let aligns = zipWith alignType rawHeadsList lengths
|
||||
let rawHeads = if headless
|
||||
then replicate (length dashes) ""
|
||||
then []
|
||||
else map (T.unlines . map trim) rawHeadsList
|
||||
heads <- fmap sequence $
|
||||
mapM (parseFromString' (mconcat <$> many plain).trim) rawHeads
|
||||
|
@ -1292,7 +1292,7 @@ multilineTableHeader headless = try $ do
|
|||
-- which may be grid, separated by blank lines, and
|
||||
-- ending with a footer (dashed line followed by blank line).
|
||||
gridTable :: PandocMonad m => Bool -- ^ Headerless table
|
||||
-> MarkdownParser m ([Alignment], [Double], F [Blocks], F [[Blocks]])
|
||||
-> MarkdownParser m ([Alignment], [Double], F [Pandoc.Row], F [Pandoc.Row])
|
||||
gridTable headless = gridTableWith' parseBlocks headless
|
||||
|
||||
pipeBreak :: PandocMonad m => MarkdownParser m ([Alignment], [Int])
|
||||
|
@ -1307,7 +1307,7 @@ pipeBreak = try $ do
|
|||
blankline
|
||||
return $ unzip (first:rest)
|
||||
|
||||
pipeTable :: PandocMonad m => MarkdownParser m ([Alignment], [Double], F [Blocks], F [[Blocks]])
|
||||
pipeTable :: PandocMonad m => MarkdownParser m ([Alignment], [Double], F [Pandoc.Row], F [Pandoc.Row])
|
||||
pipeTable = try $ do
|
||||
nonindentSpaces
|
||||
lookAhead nonspaceChar
|
||||
|
@ -1323,7 +1323,7 @@ pipeTable = try $ do
|
|||
fromIntegral len / fromIntegral (sum seplengths))
|
||||
seplengths
|
||||
else replicate (length aligns) 0.0
|
||||
return (aligns, widths, heads', sequence lines'')
|
||||
return (aligns, widths, toHeaderRow <$> heads', map toRow <$> sequence lines'')
|
||||
|
||||
sepPipe :: PandocMonad m => MarkdownParser m ()
|
||||
sepPipe = try $ do
|
||||
|
@ -1384,7 +1384,7 @@ tableWith :: PandocMonad m
|
|||
-> ([Int] -> MarkdownParser m (F [Blocks]))
|
||||
-> MarkdownParser m sep
|
||||
-> MarkdownParser m end
|
||||
-> MarkdownParser m ([Alignment], [Double], F [Blocks], F [[Blocks]])
|
||||
-> MarkdownParser m ([Alignment], [Double], F [Pandoc.Row], F [Pandoc.Row])
|
||||
tableWith headerParser rowParser lineParser footerParser = try $ do
|
||||
(heads, aligns, indices) <- headerParser
|
||||
lines' <- fmap sequence $ rowParser indices `sepEndBy1` lineParser
|
||||
|
@ -1393,7 +1393,7 @@ tableWith headerParser rowParser lineParser footerParser = try $ do
|
|||
let widths = if null indices
|
||||
then replicate (length aligns) 0.0
|
||||
else widthsFromIndices numColumns indices
|
||||
return (aligns, widths, heads, lines')
|
||||
return (aligns, widths, toHeaderRow <$> heads, map toRow <$> lines')
|
||||
|
||||
table :: PandocMonad m => MarkdownParser m (F Blocks)
|
||||
table = try $ do
|
||||
|
@ -1424,7 +1424,11 @@ table = try $ do
|
|||
caption' <- caption
|
||||
heads' <- heads
|
||||
lns' <- lns
|
||||
return $ B.table caption' (zip aligns (strictPos <$> widths')) heads' lns'
|
||||
return $ B.table (B.simpleCaption $ B.plain caption')
|
||||
(zip aligns (strictPos <$> widths'))
|
||||
(TableHead nullAttr heads')
|
||||
[TableBody nullAttr 0 [] lns']
|
||||
(TableFoot nullAttr [])
|
||||
|
||||
--
|
||||
-- inline
|
||||
|
@ -2113,3 +2117,9 @@ doubleQuoted = try $ do
|
|||
withQuoteContext InDoubleQuote $
|
||||
fmap B.doubleQuoted . trimInlinesF . mconcat <$>
|
||||
many1Till inline doubleQuoteEnd
|
||||
|
||||
toRow :: [Blocks] -> Pandoc.Row
|
||||
toRow = Row nullAttr . map B.simpleCell
|
||||
|
||||
toHeaderRow :: [Blocks] -> [Pandoc.Row]
|
||||
toHeaderRow l = if null l then [] else [toRow l]
|
||||
|
|
|
@ -232,7 +232,13 @@ table = do
|
|||
let (headers,rows) = if hasheader
|
||||
then (hdr, rows')
|
||||
else (replicate cols mempty, hdr:rows')
|
||||
return $ B.table caption cellspecs headers rows
|
||||
let toRow = Row nullAttr . map B.simpleCell
|
||||
toHeaderRow l = if null l then [] else [toRow l]
|
||||
return $ B.table (B.simpleCaption $ B.plain caption)
|
||||
cellspecs
|
||||
(TableHead nullAttr $ toHeaderRow headers)
|
||||
[TableBody nullAttr 0 [] $ map toRow rows]
|
||||
(TableFoot nullAttr [])
|
||||
|
||||
parseAttrs :: PandocMonad m => MWParser m [(Text,Text)]
|
||||
parseAttrs = many1 parseAttr
|
||||
|
|
|
@ -645,9 +645,15 @@ data MuseTableElement = MuseHeaderRow [Blocks]
|
|||
|
||||
museToPandocTable :: MuseTable -> Blocks
|
||||
museToPandocTable (MuseTable caption headers body footers) =
|
||||
B.table caption attrs headRow (rows ++ body ++ footers)
|
||||
B.table (B.simpleCaption $ B.plain caption)
|
||||
attrs
|
||||
(TableHead nullAttr $ toHeaderRow headRow)
|
||||
[TableBody nullAttr 0 [] $ map toRow $ rows ++ body ++ footers]
|
||||
(TableFoot nullAttr [])
|
||||
where attrs = (AlignDefault, ColWidthDefault) <$ transpose (headers ++ body ++ footers)
|
||||
(headRow, rows) = fromMaybe ([], []) $ uncons headers
|
||||
toRow = Row nullAttr . map B.simpleCell
|
||||
toHeaderRow l = if null l then [] else [toRow l]
|
||||
|
||||
museAppendElement :: MuseTableElement
|
||||
-> MuseTable
|
||||
|
@ -693,8 +699,13 @@ museGridTable = try $ do
|
|||
indent <- getIndent
|
||||
indices <- museGridTableHeader
|
||||
fmap rowsToTable . sequence <$> many1 (museGridTableRow indent indices)
|
||||
where rowsToTable rows = B.table mempty attrs [] rows
|
||||
where rowsToTable rows = B.table B.emptyCaption
|
||||
attrs
|
||||
(TableHead nullAttr [])
|
||||
[TableBody nullAttr 0 [] $ map toRow rows]
|
||||
(TableFoot nullAttr [])
|
||||
where attrs = (AlignDefault, ColWidthDefault) <$ transpose rows
|
||||
toRow = Row nullAttr . map B.simpleCell
|
||||
|
||||
-- | Parse a table.
|
||||
table :: PandocMonad m => MuseParser m (F Blocks)
|
||||
|
|
|
@ -627,8 +627,14 @@ orgToPandocTable (OrgTable colProps heads lns) caption =
|
|||
let totalWidth = if any (isJust . columnRelWidth) colProps
|
||||
then Just . sum $ map (fromMaybe 1 . columnRelWidth) colProps
|
||||
else Nothing
|
||||
in B.table caption (map (convertColProp totalWidth) colProps) heads lns
|
||||
in B.table (B.simpleCaption $ B.plain caption)
|
||||
(map (convertColProp totalWidth) colProps)
|
||||
(TableHead nullAttr $ toHeaderRow heads)
|
||||
[TableBody nullAttr 0 [] $ map toRow lns]
|
||||
(TableFoot nullAttr [])
|
||||
where
|
||||
toRow = Row nullAttr . map B.simpleCell
|
||||
toHeaderRow l = if null l then [] else [toRow l]
|
||||
convertColProp :: Maybe Int -> ColumnProperty -> (Alignment, ColWidth)
|
||||
convertColProp totalWidth colProp =
|
||||
let
|
||||
|
|
|
@ -822,10 +822,13 @@ listTableDirective top fields body = do
|
|||
Just specs -> normWidths $ map (fromMaybe (0 :: Double) . safeRead) $
|
||||
splitTextBy (`elem` (" ," :: String)) specs
|
||||
_ -> replicate numOfCols ColWidthDefault
|
||||
return $ B.table title
|
||||
toRow = Row nullAttr . map B.simpleCell
|
||||
toHeaderRow l = if null l then [] else [toRow l]
|
||||
return $ B.table (B.simpleCaption $ B.plain title)
|
||||
(zip (replicate numOfCols AlignDefault) widths)
|
||||
headerRow
|
||||
bodyRows
|
||||
(TableHead nullAttr $ toHeaderRow headerRow)
|
||||
[TableBody nullAttr 0 [] $ map toRow bodyRows]
|
||||
(TableFoot nullAttr [])
|
||||
where takeRows [BulletList rows] = map takeCells rows
|
||||
takeRows _ = []
|
||||
takeCells [BulletList cells] = map B.fromList cells
|
||||
|
@ -897,10 +900,13 @@ csvTableDirective top fields rawcsv = do
|
|||
$ map (fromMaybe (0 :: Double) . safeRead)
|
||||
$ splitTextBy (`elem` (" ," :: String)) specs
|
||||
_ -> replicate numOfCols ColWidthDefault
|
||||
return $ B.table title
|
||||
(zip (replicate numOfCols AlignDefault) widths)
|
||||
headerRow
|
||||
bodyRows
|
||||
let toRow = Row nullAttr . map B.simpleCell
|
||||
toHeaderRow l = if null l then [] else [toRow l]
|
||||
return $ B.table (B.simpleCaption $ B.plain title)
|
||||
(zip (replicate numOfCols AlignDefault) widths)
|
||||
(TableHead nullAttr $ toHeaderRow headerRow)
|
||||
[TableBody nullAttr 0 [] $ map toRow bodyRows]
|
||||
(TableFoot nullAttr [])
|
||||
|
||||
-- TODO:
|
||||
-- - Only supports :format: fields with a single format for :raw: roles,
|
||||
|
|
|
@ -228,10 +228,16 @@ table = try $ do
|
|||
return $ buildTable mempty rows $ fromMaybe (align rows, columns rows) tableHead
|
||||
where
|
||||
buildTable caption rows (aligns, heads)
|
||||
= B.table caption aligns heads rows
|
||||
= B.table (B.simpleCaption $ B.plain caption)
|
||||
aligns
|
||||
(TableHead nullAttr $ toHeaderRow heads)
|
||||
[TableBody nullAttr 0 [] $ map toRow rows]
|
||||
(TableFoot nullAttr [])
|
||||
align rows = replicate (columCount rows) (AlignDefault, ColWidthDefault)
|
||||
columns rows = replicate (columCount rows) mempty
|
||||
columCount rows = length $ head rows
|
||||
toRow = Row nullAttr . map B.simpleCell
|
||||
toHeaderRow l = if null l then [] else [toRow l]
|
||||
|
||||
tableParseHeader :: PandocMonad m => TWParser m ((Alignment, ColWidth), B.Blocks)
|
||||
tableParseHeader = try $ do
|
||||
|
|
|
@ -377,10 +377,13 @@ table = try $ do
|
|||
_ -> (mempty, rawrows)
|
||||
let nbOfCols = maximum $ map length (headers:rows)
|
||||
let aligns = map minimum $ transpose $ map (map (snd . fst)) (headers:rows)
|
||||
return $ B.table caption
|
||||
let toRow = Row nullAttr . map B.simpleCell
|
||||
toHeaderRow l = if null l then [] else [toRow l]
|
||||
return $ B.table (B.simpleCaption $ B.plain caption)
|
||||
(zip aligns (replicate nbOfCols ColWidthDefault))
|
||||
(map snd headers)
|
||||
(map (map snd) rows)
|
||||
(TableHead nullAttr $ toHeaderRow $ map snd headers)
|
||||
[TableBody nullAttr 0 [] $ map (toRow . map snd) rows]
|
||||
(TableFoot nullAttr [])
|
||||
|
||||
-- | Ignore markers for cols, thead, tfoot.
|
||||
ignorableRow :: PandocMonad m => ParserT Text ParserState m ()
|
||||
|
|
|
@ -267,9 +267,13 @@ table = try $ do
|
|||
let size = maximum (map length rows')
|
||||
let rowsPadded = map (pad size) rows'
|
||||
let headerPadded = if null tableHeader then mempty else pad size tableHeader
|
||||
return $ B.table mempty
|
||||
let toRow = Row nullAttr . map B.simpleCell
|
||||
toHeaderRow l = if null l then [] else [toRow l]
|
||||
return $ B.table B.emptyCaption
|
||||
(zip aligns (replicate ncolumns ColWidthDefault))
|
||||
headerPadded rowsPadded
|
||||
(TableHead nullAttr $ toHeaderRow headerPadded)
|
||||
[TableBody nullAttr 0 [] $ map toRow rowsPadded]
|
||||
(TableFoot nullAttr [])
|
||||
|
||||
pad :: (Monoid a) => Int -> [a] -> [a]
|
||||
pad n xs = xs ++ replicate (n - length xs) mempty
|
||||
|
|
|
@ -280,7 +280,7 @@ blockToDocbook opts (Table _ blkCapt specs thead tbody tfoot) = do
|
|||
body' <- (inTagsIndented "tbody" . vcat) <$>
|
||||
mapM (tableRowToDocbook opts) rows
|
||||
return $ inTagsIndented tableType $ captionDoc $$
|
||||
inTags True "tgroup" [("cols", tshow (length headers))] (
|
||||
inTags True "tgroup" [("cols", tshow (length aligns))] (
|
||||
coltags $$ head' $$ body')
|
||||
|
||||
hasLineBreaks :: [Inline] -> Bool
|
||||
|
|
|
@ -336,10 +336,10 @@ blockToXml h@Header{} = do
|
|||
blockToXml HorizontalRule = return [ el "empty-line" () ]
|
||||
blockToXml (Table _ blkCapt specs thead tbody tfoot) = do
|
||||
let (caption, aligns, _, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
hd <- mkrow "th" headers aligns
|
||||
hd <- if null headers then pure [] else (:[]) <$> mkrow "th" headers aligns
|
||||
bd <- mapM (\r -> mkrow "td" r aligns) rows
|
||||
c <- el "emphasis" <$> cMapM toXml caption
|
||||
return [el "table" (hd : bd), el "p" c]
|
||||
return [el "table" (hd <> bd), el "p" c]
|
||||
where
|
||||
mkrow :: PandocMonad m => String -> [[Block]] -> [Alignment] -> FBM m Content
|
||||
mkrow tag cells aligns' =
|
||||
|
|
|
@ -196,7 +196,7 @@ blockToTEI _ HorizontalRule = return $
|
|||
-- table info in the AST is here lossily discard.
|
||||
blockToTEI opts (Table _ blkCapt specs thead tbody tfoot) = do
|
||||
let (_, _, _, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
headers' <- tableHeadersToTEI opts headers
|
||||
headers' <- if null headers then pure mempty else tableHeadersToTEI opts headers
|
||||
rows' <- mapM (tableRowToTEI opts) rows
|
||||
return $ inTags True "table" [] $ headers' $$ vcat rows'
|
||||
|
||||
|
|
|
@ -125,7 +125,7 @@ blockToXWiki (DefinitionList items) = do
|
|||
-- TODO: support more features
|
||||
blockToXWiki (Table _ blkCapt specs thead tbody tfoot) = do
|
||||
let (_, _, _, headers, rows') = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
headers' <- mapM (tableCellXWiki True) headers
|
||||
headers' <- mapM (tableCellXWiki True) $ take (length specs) $ headers ++ repeat []
|
||||
otherRows <- mapM formRow rows'
|
||||
return $ Text.unlines (Text.unwords headers':otherRows)
|
||||
|
||||
|
|
|
@ -15,7 +15,7 @@ extra-deps:
|
|||
# - pandoc-types-1.20
|
||||
# better-tables
|
||||
- git: git@github.com:despresc/pandoc-types
|
||||
commit: bb3148188746b8cb375f93af1ea3095db8f1f720
|
||||
commit: 09cb4314010365abc4512c2363b83711c92ac18b
|
||||
- texmath-0.12.0.1
|
||||
- haddock-library-1.8.0
|
||||
- skylighting-0.8.3.2
|
||||
|
|
|
@ -296,31 +296,22 @@ tests = [ testGroup "inlines"
|
|||
T.unlines [ "| foo | bar |"
|
||||
, "| bat | baz |"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
|
||||
[]
|
||||
[[plain "foo", plain "bar"]
|
||||
,[plain "bat", plain "baz"]]
|
||||
simpleTable [] [[plain "foo", plain "bar"]
|
||||
,[plain "bat", plain "baz"]]
|
||||
, "Table with header" =:
|
||||
T.unlines [ "^ foo ^ bar ^"
|
||||
, "| bat | baz |"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
|
||||
[plain "foo", plain "bar"]
|
||||
[[plain "bat", plain "baz"]]
|
||||
simpleTable [plain "foo", plain "bar"] [[plain "bat", plain "baz"]]
|
||||
, "Table with colspan" =:
|
||||
T.unlines [ "^ 0,0 ^ 0,1 ^ 0,2 ^"
|
||||
, "| 1,0 | 1,1 ||"
|
||||
, "| 2,0 | 2,1 | 2,2 |"
|
||||
] =?>
|
||||
table
|
||||
mempty
|
||||
[(AlignDefault, ColWidthDefault)
|
||||
,(AlignDefault, ColWidthDefault)
|
||||
,(AlignDefault, ColWidthDefault)]
|
||||
[plain "0,0", plain "0,1", plain "0,2"]
|
||||
[[plain "1,0", plain "1,1", mempty]
|
||||
,[plain "2,0", plain "2,1", plain "2,2"]
|
||||
]
|
||||
simpleTable [plain "0,0", plain "0,1", plain "0,2"]
|
||||
[[plain "1,0", plain "1,1", mempty]
|
||||
,[plain "2,0", plain "2,1", plain "2,2"]
|
||||
]
|
||||
, "Indented code block" =:
|
||||
T.unlines [ "foo"
|
||||
, " bar"
|
||||
|
|
|
@ -36,8 +36,14 @@ infix 4 =:
|
|||
(=:) = test latex
|
||||
|
||||
simpleTable' :: [Alignment] -> [[Blocks]] -> Blocks
|
||||
simpleTable' aligns = table "" (zip aligns (repeat ColWidthDefault))
|
||||
(map (const mempty) aligns)
|
||||
simpleTable' aligns rows
|
||||
= table emptyCaption
|
||||
(zip aligns (repeat ColWidthDefault))
|
||||
(TableHead nullAttr [])
|
||||
[TableBody nullAttr 0 [] $ map toRow rows]
|
||||
(TableFoot nullAttr [])
|
||||
where
|
||||
toRow = Row nullAttr . map simpleCell
|
||||
|
||||
tokUntokRt :: String -> Bool
|
||||
tokUntokRt s = untokenize (tokenize "random" t) == t
|
||||
|
|
|
@ -30,6 +30,9 @@ infix 4 =:
|
|||
=> String -> (Text, c) -> TestTree
|
||||
(=:) = test man
|
||||
|
||||
toRow :: [Blocks] -> Row
|
||||
toRow = Row nullAttr . map simpleCell
|
||||
|
||||
tests :: [TestTree]
|
||||
tests = [
|
||||
-- .SH "HEllo bbb" "aaa"" as"
|
||||
|
@ -122,16 +125,21 @@ tests = [
|
|||
testGroup "Tables" [
|
||||
"t1" =:
|
||||
".TS\nallbox;\nl l l.\na\tb\tc\nd\te\tf\n.TE"
|
||||
=?> table mempty (replicate 3 (AlignLeft, ColWidthDefault)) [] [
|
||||
map (plain . str ) ["a", "b", "c"],
|
||||
map (plain . str ) ["d", "e", "f"]
|
||||
],
|
||||
=?> table
|
||||
emptyCaption
|
||||
(replicate 3 (AlignLeft, ColWidthDefault))
|
||||
(TableHead nullAttr [])
|
||||
[TableBody nullAttr 0 [] $ map toRow
|
||||
[map (plain . str ) ["a", "b", "c"],
|
||||
map (plain . str ) ["d", "e", "f"]]]
|
||||
(TableFoot nullAttr []),
|
||||
"longcell" =:
|
||||
".TS\n;\nr.\nT{\na\nb\nc d\nT}\nf\n.TE"
|
||||
=?> table
|
||||
mempty
|
||||
emptyCaption
|
||||
[(AlignRight, ColWidthDefault)]
|
||||
[]
|
||||
[[plain $ text "a b c d"], [plain $ str "f"]]
|
||||
(TableHead nullAttr [])
|
||||
[TableBody nullAttr 0 [] $ map toRow [[plain $ text "a b c d"], [plain $ str "f"]]]
|
||||
(TableFoot nullAttr [])
|
||||
]
|
||||
]
|
||||
|
|
|
@ -43,6 +43,17 @@ infix 4 =:
|
|||
spcSep :: [Inlines] -> Inlines
|
||||
spcSep = mconcat . intersperse space
|
||||
|
||||
simpleTable' :: Int -> Caption -> [Blocks] -> [[Blocks]] -> Blocks
|
||||
simpleTable' n capt headers rows
|
||||
= table capt
|
||||
(replicate n (AlignDefault, ColWidthDefault))
|
||||
(TableHead nullAttr $ toHeaderRow headers)
|
||||
[TableBody nullAttr 0 [] $ map toRow rows]
|
||||
(TableFoot nullAttr [])
|
||||
where
|
||||
toRow = Row nullAttr . map simpleCell
|
||||
toHeaderRow l = if null l then [] else [toRow l]
|
||||
|
||||
-- Tables don't round-trip yet
|
||||
--
|
||||
makeRoundTrip :: Block -> Block
|
||||
|
@ -982,14 +993,10 @@ tests =
|
|||
, testGroup "Tables"
|
||||
[ "Two cell table" =:
|
||||
"One | Two" =?>
|
||||
table mempty [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
|
||||
[]
|
||||
[[plain "One", plain "Two"]]
|
||||
simpleTable [] [[plain "One", plain "Two"]]
|
||||
, "Table with multiple words" =:
|
||||
"One two | three four" =?>
|
||||
table mempty [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
|
||||
[]
|
||||
[[plain "One two", plain "three four"]]
|
||||
simpleTable [] [[plain "One two", plain "three four"]]
|
||||
, "Not a table" =:
|
||||
"One| Two" =?>
|
||||
para (text "One| Two")
|
||||
|
@ -1001,38 +1008,30 @@ tests =
|
|||
[ "One | Two"
|
||||
, "Three | Four"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
|
||||
[]
|
||||
[[plain "One", plain "Two"],
|
||||
[plain "Three", plain "Four"]]
|
||||
simpleTable [] [[plain "One", plain "Two"],
|
||||
[plain "Three", plain "Four"]]
|
||||
, "Table with one header" =:
|
||||
T.unlines
|
||||
[ "First || Second"
|
||||
, "Third | Fourth"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
|
||||
[plain "First", plain "Second"]
|
||||
[[plain "Third", plain "Fourth"]]
|
||||
simpleTable [plain "First", plain "Second"] [[plain "Third", plain "Fourth"]]
|
||||
, "Table with two headers" =:
|
||||
T.unlines
|
||||
[ "First || header"
|
||||
, "Second || header"
|
||||
, "Foo | bar"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
|
||||
[plain "First", plain "header"]
|
||||
[[plain "Second", plain "header"],
|
||||
[plain "Foo", plain "bar"]]
|
||||
simpleTable [plain "First", plain "header"] [[plain "Second", plain "header"],
|
||||
[plain "Foo", plain "bar"]]
|
||||
, "Header and footer reordering" =:
|
||||
T.unlines
|
||||
[ "Foo ||| bar"
|
||||
, "Baz || foo"
|
||||
, "Bar | baz"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
|
||||
[plain "Baz", plain "foo"]
|
||||
[[plain "Bar", plain "baz"],
|
||||
[plain "Foo", plain "bar"]]
|
||||
simpleTable [plain "Baz", plain "foo"] [[plain "Bar", plain "baz"],
|
||||
[plain "Foo", plain "bar"]]
|
||||
, "Table with caption" =:
|
||||
T.unlines
|
||||
[ "Foo || bar || baz"
|
||||
|
@ -1040,32 +1039,30 @@ tests =
|
|||
, "Second | row | there"
|
||||
, "|+ Table caption +|"
|
||||
] =?>
|
||||
table (text "Table caption") (replicate 3 (AlignDefault, ColWidthDefault))
|
||||
[plain "Foo", plain "bar", plain "baz"]
|
||||
[[plain "First", plain "row", plain "here"],
|
||||
[plain "Second", plain "row", plain "there"]]
|
||||
simpleTable' 3 (simpleCaption $ plain $ text "Table caption")
|
||||
[plain "Foo", plain "bar", plain "baz"]
|
||||
[[plain "First", plain "row", plain "here"],
|
||||
[plain "Second", plain "row", plain "there"]]
|
||||
, "Table caption with +" =:
|
||||
T.unlines
|
||||
[ "Foo | bar"
|
||||
, "|+ Table + caption +|"
|
||||
] =?>
|
||||
table (text "Table + caption") (replicate 2 (AlignDefault, ColWidthDefault))
|
||||
[]
|
||||
[[plain "Foo", plain "bar"]]
|
||||
simpleTable' 2 (simpleCaption $ plain $ text "Table + caption")
|
||||
[]
|
||||
[[plain "Foo", plain "bar"]]
|
||||
, "Caption without table" =:
|
||||
"|+ Foo bar baz +|" =?>
|
||||
table (text "Foo bar baz") [] [] []
|
||||
simpleTable' 0 (simpleCaption $ plain $ text "Foo bar baz") [] []
|
||||
, "Table indented with space" =:
|
||||
T.unlines
|
||||
[ " Foo | bar"
|
||||
, " Baz | foo"
|
||||
, " Bar | baz"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
|
||||
[]
|
||||
[[plain "Foo", plain "bar"],
|
||||
[plain "Baz", plain "foo"],
|
||||
[plain "Bar", plain "baz"]]
|
||||
simpleTable [] [[plain "Foo", plain "bar"],
|
||||
[plain "Baz", plain "foo"],
|
||||
[plain "Bar", plain "baz"]]
|
||||
, "Empty cells" =:
|
||||
T.unlines
|
||||
[ " | Foo"
|
||||
|
@ -1073,42 +1070,33 @@ tests =
|
|||
, " bar |"
|
||||
, " || baz"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
|
||||
[plain "", plain "baz"]
|
||||
[[plain "", plain "Foo"],
|
||||
[plain "", plain ""],
|
||||
[plain "bar", plain ""]]
|
||||
simpleTable [plain "", plain "baz"] [[plain "", plain "Foo"],
|
||||
[plain "", plain ""],
|
||||
[plain "bar", plain ""]]
|
||||
, "Empty cell in the middle" =:
|
||||
T.unlines
|
||||
[ " 1 | 2 | 3"
|
||||
, " 4 | | 6"
|
||||
, " 7 | 8 | 9"
|
||||
] =?>
|
||||
table mempty [ (AlignDefault, ColWidthDefault)
|
||||
, (AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
|
||||
[]
|
||||
[[plain "1", plain "2", plain "3"],
|
||||
[plain "4", mempty, plain "6"],
|
||||
[plain "7", plain "8", plain "9"]]
|
||||
simpleTable []
|
||||
[[plain "1", plain "2", plain "3"],
|
||||
[plain "4", mempty, plain "6"],
|
||||
[plain "7", plain "8", plain "9"]]
|
||||
, "Grid table" =:
|
||||
T.unlines
|
||||
[ "+-----+-----+"
|
||||
, "| foo | bar |"
|
||||
, "+-----+-----+"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
|
||||
[]
|
||||
[[para "foo", para "bar"]]
|
||||
simpleTable [] [[para "foo", para "bar"]]
|
||||
, "Grid table inside list" =:
|
||||
T.unlines
|
||||
[ " - +-----+-----+"
|
||||
, " | foo | bar |"
|
||||
, " +-----+-----+"
|
||||
] =?>
|
||||
bulletList [table mempty [ (AlignDefault, ColWidthDefault)
|
||||
, (AlignDefault, ColWidthDefault)]
|
||||
[]
|
||||
[[para "foo", para "bar"]]]
|
||||
bulletList [simpleTable [] [[para "foo", para "bar"]]]
|
||||
, "Grid table with two rows" =:
|
||||
T.unlines
|
||||
[ "+-----+-----+"
|
||||
|
@ -1117,10 +1105,8 @@ tests =
|
|||
, "| bat | baz |"
|
||||
, "+-----+-----+"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
|
||||
[]
|
||||
[[para "foo", para "bar"]
|
||||
,[para "bat", para "baz"]]
|
||||
simpleTable [] [[para "foo", para "bar"]
|
||||
,[para "bat", para "baz"]]
|
||||
, "Grid table inside grid table" =:
|
||||
T.unlines
|
||||
[ "+-----+"
|
||||
|
@ -1129,11 +1115,7 @@ tests =
|
|||
, "|+---+|"
|
||||
, "+-----+"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, ColWidthDefault)]
|
||||
[]
|
||||
[[table mempty [(AlignDefault, ColWidthDefault)]
|
||||
[]
|
||||
[[para "foo"]]]]
|
||||
simpleTable [] [[simpleTable [] [[para "foo"]]]]
|
||||
, "Grid table with example" =:
|
||||
T.unlines
|
||||
[ "+------------+"
|
||||
|
@ -1142,9 +1124,7 @@ tests =
|
|||
, "| </example> |"
|
||||
, "+------------+"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, ColWidthDefault)]
|
||||
[]
|
||||
[[codeBlock "foo"]]
|
||||
simpleTable [] [[codeBlock "foo"]]
|
||||
]
|
||||
, testGroup "Lists"
|
||||
[ "Bullet list" =:
|
||||
|
@ -1513,19 +1493,11 @@ tests =
|
|||
]
|
||||
, "Definition list with table" =:
|
||||
" foo :: bar | baz" =?>
|
||||
definitionList [ ("foo", [ table mempty [ (AlignDefault, ColWidthDefault)
|
||||
, (AlignDefault, ColWidthDefault)]
|
||||
[]
|
||||
[[plain "bar", plain "baz"]]
|
||||
definitionList [ ("foo", [ simpleTable [] [[plain "bar", plain "baz"]]
|
||||
])]
|
||||
, "Definition list with table inside bullet list" =:
|
||||
" - foo :: bar | baz" =?>
|
||||
bulletList [definitionList [ ("foo", [ table
|
||||
mempty
|
||||
[ (AlignDefault, ColWidthDefault)
|
||||
, (AlignDefault, ColWidthDefault) ]
|
||||
[]
|
||||
[[plain "bar", plain "baz"]]
|
||||
bulletList [definitionList [ ("foo", [ simpleTable [] [[plain "bar", plain "baz"]]
|
||||
])]]
|
||||
, test emacsMuse "Multi-line definition lists from Emacs Muse manual"
|
||||
(T.unlines
|
||||
|
|
|
@ -24,7 +24,18 @@ simpleTable' :: Int
|
|||
-> [Blocks]
|
||||
-> [[Blocks]]
|
||||
-> Blocks
|
||||
simpleTable' n = table "" (replicate n (AlignDefault, ColWidthDefault))
|
||||
simpleTable' n = simpleTable'' emptyCaption $ replicate n (AlignDefault, ColWidthDefault)
|
||||
|
||||
simpleTable'' :: Caption -> [ColSpec] -> [Blocks] -> [[Blocks]] -> Blocks
|
||||
simpleTable'' capt spec headers rows
|
||||
= table capt
|
||||
spec
|
||||
(TableHead nullAttr $ toHeaderRow headers)
|
||||
[TableBody nullAttr 0 [] $ map toRow rows]
|
||||
(TableFoot nullAttr [])
|
||||
where
|
||||
toRow = Row nullAttr . map simpleCell
|
||||
toHeaderRow l = if null l then [] else [toRow l]
|
||||
|
||||
tests :: [TestTree]
|
||||
tests =
|
||||
|
@ -121,14 +132,16 @@ tests =
|
|||
, "| 1 | One | foo |"
|
||||
, "| 2 | Two | bar |"
|
||||
] =?>
|
||||
table "" (zip
|
||||
[AlignCenter, AlignRight, AlignDefault]
|
||||
[ColWidthDefault, ColWidthDefault, ColWidthDefault])
|
||||
[]
|
||||
[ [ plain "Numbers", plain "Text", plain "More" ]
|
||||
, [ plain "1" , plain "One" , plain "foo" ]
|
||||
, [ plain "2" , plain "Two" , plain "bar" ]
|
||||
]
|
||||
simpleTable''
|
||||
emptyCaption
|
||||
(zip
|
||||
[AlignCenter, AlignRight, AlignDefault]
|
||||
[ColWidthDefault, ColWidthDefault, ColWidthDefault])
|
||||
[]
|
||||
[ [ plain "Numbers", plain "Text", plain "More" ]
|
||||
, [ plain "1" , plain "One" , plain "foo" ]
|
||||
, [ plain "2" , plain "Two" , plain "bar" ]
|
||||
]
|
||||
|
||||
, "Pipe within text doesn't start a table" =:
|
||||
"Ceci n'est pas une | pipe " =?>
|
||||
|
@ -145,23 +158,26 @@ tests =
|
|||
, "| 1 | One | foo |"
|
||||
, "| 2"
|
||||
] =?>
|
||||
table "" (zip [AlignCenter, AlignRight] [ColWidthDefault, ColWidthDefault])
|
||||
[ plain "Numbers", plain "Text" ]
|
||||
[ [ plain "1" , plain "One" , plain "foo" ]
|
||||
, [ plain "2" ]
|
||||
]
|
||||
simpleTable''
|
||||
emptyCaption
|
||||
(zip [AlignCenter, AlignRight] [ColWidthDefault, ColWidthDefault])
|
||||
[ plain "Numbers", plain "Text" ]
|
||||
[ [ plain "1" , plain "One" , plain "foo" ]
|
||||
, [ plain "2" ]
|
||||
]
|
||||
|
||||
, "Table with caption" =:
|
||||
T.unlines [ "#+CAPTION: Hitchhiker's Multiplication Table"
|
||||
, "| x | 6 |"
|
||||
, "| 9 | 42 |"
|
||||
] =?>
|
||||
table "Hitchhiker's Multiplication Table"
|
||||
[(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
|
||||
[]
|
||||
[ [ plain "x", plain "6" ]
|
||||
, [ plain "9", plain "42" ]
|
||||
]
|
||||
simpleTable''
|
||||
(simpleCaption $ plain "Hitchhiker's Multiplication Table")
|
||||
[(AlignDefault, ColWidthDefault), (AlignDefault, ColWidthDefault)]
|
||||
[]
|
||||
[ [ plain "x", plain "6" ]
|
||||
, [ plain "9", plain "42" ]
|
||||
]
|
||||
|
||||
, "named table" =:
|
||||
T.unlines [ "#+NAME: x-marks-the-spot"
|
||||
|
|
|
@ -44,7 +44,18 @@ simpleTable' :: Int
|
|||
-> [Blocks]
|
||||
-> [[Blocks]]
|
||||
-> Blocks
|
||||
simpleTable' n = table "" (replicate n (AlignCenter, ColWidthDefault))
|
||||
simpleTable' n = simpleTable'' $ replicate n (AlignCenter, ColWidthDefault)
|
||||
|
||||
simpleTable'' :: [ColSpec] -> [Blocks] -> [[Blocks]] -> Blocks
|
||||
simpleTable'' spec headers rows
|
||||
= table emptyCaption
|
||||
spec
|
||||
(TableHead nullAttr $ toHeaderRow headers)
|
||||
[TableBody nullAttr 0 [] $ map toRow rows]
|
||||
(TableFoot nullAttr [])
|
||||
where
|
||||
toRow = Row nullAttr . map simpleCell
|
||||
toHeaderRow l = if null l then [] else [toRow l]
|
||||
|
||||
tests :: [TestTree]
|
||||
tests =
|
||||
|
@ -398,14 +409,15 @@ tests =
|
|||
, "| 1 | One | foo |"
|
||||
, "| 2 | Two | bar |"
|
||||
] =?>
|
||||
table "" (zip
|
||||
[AlignCenter, AlignRight, AlignDefault]
|
||||
[ColWidthDefault, ColWidthDefault, ColWidthDefault])
|
||||
[]
|
||||
[ [ plain "Numbers", plain "Text", plain "More" ]
|
||||
, [ plain "1" , plain "One" , plain "foo" ]
|
||||
, [ plain "2" , plain "Two" , plain "bar" ]
|
||||
]
|
||||
simpleTable''
|
||||
(zip
|
||||
[AlignCenter, AlignRight, AlignDefault]
|
||||
[ColWidthDefault, ColWidthDefault, ColWidthDefault])
|
||||
[]
|
||||
[ [ plain "Numbers", plain "Text", plain "More" ]
|
||||
, [ plain "1" , plain "One" , plain "foo" ]
|
||||
, [ plain "2" , plain "Two" , plain "bar" ]
|
||||
]
|
||||
|
||||
, "Pipe within text doesn't start a table" =:
|
||||
"Ceci n'est pas une | pipe " =?>
|
||||
|
@ -417,13 +429,14 @@ tests =
|
|||
, "| 1 | One | foo |"
|
||||
, "| 2 "
|
||||
] =?>
|
||||
table "" (zip
|
||||
[AlignCenter, AlignLeft, AlignLeft]
|
||||
[ColWidthDefault, ColWidthDefault, ColWidthDefault])
|
||||
[ plain "Numbers", plain "Text" , plain mempty ]
|
||||
[ [ plain "1" , plain "One" , plain "foo" ]
|
||||
, [ plain "2" , plain mempty , plain mempty ]
|
||||
]
|
||||
simpleTable''
|
||||
(zip
|
||||
[AlignCenter, AlignLeft, AlignLeft]
|
||||
[ColWidthDefault, ColWidthDefault, ColWidthDefault])
|
||||
[ plain "Numbers", plain "Text" , plain mempty ]
|
||||
[ [ plain "1" , plain "One" , plain "foo" ]
|
||||
, [ plain "2" , plain mempty , plain mempty ]
|
||||
]
|
||||
|
||||
]
|
||||
|
||||
|
|
|
@ -116,7 +116,12 @@ tests = [ testGroup "inline code"
|
|||
plain $ text "3.2",
|
||||
plain $ text "3.3",
|
||||
plain $ text "3.4"]]
|
||||
in table capt aligns headers rows
|
||||
toRow = Row nullAttr . map simpleCell
|
||||
in table (simpleCaption $ plain capt)
|
||||
aligns
|
||||
(TableHead nullAttr [toRow headers])
|
||||
[TableBody nullAttr 0 [] $ map toRow rows]
|
||||
(TableFoot nullAttr [])
|
||||
=?> unlines [ "\\startplacetable[title={Table 1}]"
|
||||
, "\\startTABLE"
|
||||
, "\\startTABLEhead"
|
||||
|
|
|
@ -372,8 +372,12 @@ tests = [ testGroup "block elements"
|
|||
[ "table without header" =:
|
||||
let rows = [[para "Para 1.1", para "Para 1.2"]
|
||||
,[para "Para 2.1", para "Para 2.2"]]
|
||||
in table mempty [(AlignDefault,ColWidthDefault),(AlignDefault,ColWidthDefault)]
|
||||
[mempty, mempty] rows
|
||||
toRow = Row nullAttr . map simpleCell
|
||||
in table emptyCaption
|
||||
[(AlignDefault,ColWidthDefault),(AlignDefault,ColWidthDefault)]
|
||||
(TableHead nullAttr [toRow [mempty, mempty]])
|
||||
[TableBody nullAttr 0 [] $ map toRow rows]
|
||||
(TableFoot nullAttr [])
|
||||
=?>
|
||||
unlines [ " Para 1.1 | Para 1.2"
|
||||
, " Para 2.1 | Para 2.2"
|
||||
|
@ -389,12 +393,16 @@ tests = [ testGroup "block elements"
|
|||
, " Para 2.1 | Para 2.2"
|
||||
]
|
||||
, "table with header and caption" =:
|
||||
let capt = "Table 1"
|
||||
headers = [plain "header 1", plain "header 2"]
|
||||
rows = [[para "Para 1.1", para "Para 1.2"]
|
||||
,[para "Para 2.1", para "Para 2.2"]]
|
||||
in table capt [(AlignDefault,ColWidthDefault),(AlignDefault,ColWidthDefault)]
|
||||
headers rows
|
||||
let capt = simpleCaption $ plain "Table 1"
|
||||
toRow = Row nullAttr . map simpleCell
|
||||
headers = [toRow [plain "header 1", plain "header 2"]]
|
||||
rows = map toRow [[para "Para 1.1", para "Para 1.2"]
|
||||
,[para "Para 2.1", para "Para 2.2"]]
|
||||
in table capt
|
||||
[(AlignDefault,ColWidthDefault),(AlignDefault,ColWidthDefault)]
|
||||
(TableHead nullAttr headers)
|
||||
[TableBody nullAttr 0 [] rows]
|
||||
(TableFoot nullAttr [])
|
||||
=?> unlines [ " header 1 || header 2"
|
||||
, " Para 1.1 | Para 1.2"
|
||||
, " Para 2.1 | Para 2.2"
|
||||
|
|
|
@ -69,15 +69,7 @@
|
|||
,(AlignCenter,ColWidthDefault)
|
||||
,(AlignRight,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
|
|
@ -12,11 +12,7 @@
|
|||
[(AlignRight,ColWidth 8.333333333333333e-2)
|
||||
,(AlignLeft,ColWidth 0.6805555555555556)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
|
|
@ -94,11 +94,7 @@
|
|||
[(AlignDefault,ColWidthDefault)
|
||||
,(AlignDefault,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
|
|
@ -10,11 +10,7 @@
|
|||
[(AlignCenter,ColWidthDefault)
|
||||
,(AlignCenter,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
|
|
@ -20,13 +20,7 @@ Blah & Foo & Bar \\
|
|||
,(AlignRight,ColWidthDefault)
|
||||
,(AlignRight,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
|
|
@ -14,9 +14,7 @@
|
|||
[])
|
||||
[(AlignDefault,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
|
|
@ -11,9 +11,7 @@
|
|||
[])
|
||||
[(AlignCenter,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
|
|
@ -23,13 +23,7 @@ This reference to Figure \ref{fig:label} works fine.
|
|||
,(AlignCenter,ColWidthDefault)
|
||||
,(AlignRight,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
|
|
@ -511,15 +511,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Sof
|
|||
,(AlignCenter,ColWidthDefault)
|
||||
,(AlignRight,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
@ -559,15 +551,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Sof
|
|||
,(AlignRight,ColWidth 0.25)
|
||||
,(AlignLeft,ColWidth 0.25)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
|
|
@ -2,9 +2,7 @@
|
|||
[])
|
||||
[(AlignDefault,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
|
|
@ -4,13 +4,7 @@
|
|||
,(AlignDefault,ColWidthDefault)
|
||||
,(AlignDefault,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
|
|
@ -4,13 +4,7 @@
|
|||
,(AlignDefault,ColWidthDefault)
|
||||
,(AlignDefault,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
|
|
@ -51,11 +51,7 @@
|
|||
[(AlignDefault,ColWidthDefault)
|
||||
,(AlignDefault,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
@ -75,11 +71,7 @@
|
|||
[(AlignDefault,ColWidthDefault)
|
||||
,(AlignDefault,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
|
|
@ -625,13 +625,7 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl
|
|||
,(AlignDefault,ColWidthDefault)
|
||||
,(AlignDefault,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
@ -657,13 +651,7 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl
|
|||
,(AlignDefault,ColWidthDefault)
|
||||
,(AlignDefault,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
@ -689,13 +677,7 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl
|
|||
,(AlignDefault,ColWidthDefault)
|
||||
,(AlignDefault,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
@ -721,13 +703,7 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl
|
|||
,(AlignDefault,ColWidthDefault)
|
||||
,(AlignDefault,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
|
|
@ -573,13 +573,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
,(AlignLeft,ColWidthDefault)
|
||||
,(AlignLeft,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
@ -604,13 +598,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
,(AlignLeft,ColWidthDefault)
|
||||
,(AlignLeft,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
@ -635,13 +623,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
,(AlignLeft,ColWidthDefault)
|
||||
,(AlignLeft,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
@ -666,13 +648,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
,(AlignLeft,ColWidthDefault)
|
||||
,(AlignLeft,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
|
|
@ -304,9 +304,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
[])
|
||||
[(AlignCenter,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
|
|
@ -245,15 +245,7 @@ Pandoc (Meta {unMeta = fromList [("date",MetaInlines [Str "Oct",Space,Str "17,",
|
|||
,(AlignCenter,ColWidthDefault)
|
||||
,(AlignRight,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
@ -290,11 +282,7 @@ Pandoc (Meta {unMeta = fromList [("date",MetaInlines [Str "Oct",Space,Str "17,",
|
|||
[(AlignRight,ColWidth 0.5)
|
||||
,(AlignLeft,ColWidth 0.5)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
|
|
@ -10,6 +10,6 @@ Header</th><th align="left">Left
|
|||
Aligned</th><th align="right">Right
|
||||
Aligned</th><th align="left">Default aligned</th></tr><tr><td align="center">First</td><td align="left">row</td><td align="right">12.0</td><td align="left">Example of a row that spans
|
||||
multiple lines.</td></tr><tr><td align="center">Second</td><td align="left">row</td><td align="right">5.0</td><td align="left">Here’s another one. Note
|
||||
the blank line between rows.</td></tr></table><p><emphasis /></p><p>Table without column headers:</p><table><tr><th align="right" /><th align="left" /><th align="center" /><th align="right" /></tr><tr><td align="right">12</td><td align="left">12</td><td align="center">12</td><td align="right">12</td></tr><tr><td align="right">123</td><td align="left">123</td><td align="center">123</td><td align="right">123</td></tr><tr><td align="right">1</td><td align="left">1</td><td align="center">1</td><td align="right">1</td></tr></table><p><emphasis /></p><p>Multiline table without column headers:</p><table><tr><th align="center" /><th align="left" /><th align="right" /><th align="left" /></tr><tr><td align="center">First</td><td align="left">row</td><td align="right">12.0</td><td align="left">Example of a row that spans
|
||||
the blank line between rows.</td></tr></table><p><emphasis /></p><p>Table without column headers:</p><table><tr><td align="right">12</td><td align="left">12</td><td align="center">12</td><td align="right">12</td></tr><tr><td align="right">123</td><td align="left">123</td><td align="center">123</td><td align="right">123</td></tr><tr><td align="right">1</td><td align="left">1</td><td align="center">1</td><td align="right">1</td></tr></table><p><emphasis /></p><p>Multiline table without column headers:</p><table><tr><td align="center">First</td><td align="left">row</td><td align="right">12.0</td><td align="left">Example of a row that spans
|
||||
multiple lines.</td></tr><tr><td align="center">Second</td><td align="left">row</td><td align="right">5.0</td><td align="left">Here’s another one. Note
|
||||
the blank line between rows.</td></tr></table><p><emphasis /></p></section></body></FictionBook>
|
||||
|
|
|
@ -228,15 +228,7 @@
|
|||
,(AlignCenter,ColWidthDefault)
|
||||
,(AlignRight,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
@ -276,15 +268,7 @@
|
|||
,(AlignRight,ColWidth 0.1625)
|
||||
,(AlignDefault,ColWidth 0.35)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
|
|
@ -123,12 +123,6 @@
|
|||
</table>
|
||||
<p>Table without column headers:</p>
|
||||
<table>
|
||||
<row role="label">
|
||||
<cell></cell>
|
||||
<cell></cell>
|
||||
<cell></cell>
|
||||
<cell></cell>
|
||||
</row>
|
||||
<row>
|
||||
<cell><p>12</p></cell>
|
||||
<cell><p>12</p></cell>
|
||||
|
@ -150,12 +144,6 @@
|
|||
</table>
|
||||
<p>Multiline table without column headers:</p>
|
||||
<table>
|
||||
<row role="label">
|
||||
<cell></cell>
|
||||
<cell></cell>
|
||||
<cell></cell>
|
||||
<cell></cell>
|
||||
</row>
|
||||
<row>
|
||||
<cell><p>First</p></cell>
|
||||
<cell><p>row</p></cell>
|
||||
|
|
|
@ -109,13 +109,7 @@ Pandoc (Meta {unMeta = fromList []})
|
|||
,(AlignDefault,ColWidthDefault)
|
||||
,(AlignDefault,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
@ -203,13 +197,7 @@ Pandoc (Meta {unMeta = fromList []})
|
|||
,(AlignDefault,ColWidthDefault)
|
||||
,(AlignDefault,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
|
|
@ -305,9 +305,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "author"]]
|
|||
[])
|
||||
[(AlignRight,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
@ -321,13 +319,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "author"]]
|
|||
,(AlignCenter,ColWidthDefault)
|
||||
,(AlignRight,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
@ -345,13 +337,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "author"]]
|
|||
,(AlignCenter,ColWidthDefault)
|
||||
,(AlignCenter,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
@ -370,13 +356,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "author"]]
|
|||
,(AlignCenter,ColWidthDefault)
|
||||
,(AlignCenter,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
@ -489,15 +469,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "author"]]
|
|||
,(AlignCenter,ColWidthDefault)
|
||||
,(AlignCenter,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
@ -546,17 +518,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "author"]]
|
|||
,(AlignCenter,ColWidthDefault)
|
||||
,(AlignCenter,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[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 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
@ -624,17 +586,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "author"]]
|
|||
,(AlignCenter,ColWidthDefault)
|
||||
,(AlignCenter,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[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 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
@ -713,17 +665,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "author"]]
|
|||
,(AlignCenter,ColWidthDefault)
|
||||
,(AlignCenter,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[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 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
@ -805,23 +747,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "author"]]
|
|||
,(AlignCenter,ColWidthDefault)
|
||||
,(AlignCenter,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[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 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
@ -946,71 +872,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "author"]]
|
|||
,(AlignCenter,ColWidthDefault)
|
||||
,(AlignCenter,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[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 1)
|
||||
[]
|
||||
,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 1)
|
||||
[]
|
||||
,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 1)
|
||||
[]
|
||||
,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 1)
|
||||
[]
|
||||
,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 1)
|
||||
[]
|
||||
,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 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]
|
||||
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
@ -1084,9 +946,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "author"]]
|
|||
[])
|
||||
[(AlignCenter,ColWidthDefault)]
|
||||
(TableHead ("",[],[])
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
|
||||
[]]])
|
||||
[])
|
||||
[(TableBody ("",[],[]) (RowHeadColumns 0)
|
||||
[]
|
||||
[Row ("",[],[])
|
||||
|
|
Loading…
Add table
Reference in a new issue