Implement the new Table type
This commit is contained in:
parent
83c1ce1d77
commit
7254a2ae0b
114 changed files with 4842 additions and 2180 deletions
|
@ -21,6 +21,7 @@ import Foreign.Lua (Lua, Peekable, Pushable, StackIndex)
|
|||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Lua.Util (defineHowTo, pushViaConstructor)
|
||||
import Text.Pandoc.Lua.Marshaling.CommonState ()
|
||||
import Text.Pandoc.Shared (toLegacyTable)
|
||||
|
||||
import qualified Foreign.Lua as Lua
|
||||
import qualified Text.Pandoc.Lua.Util as LuaUtil
|
||||
|
@ -167,8 +168,9 @@ pushBlock = \case
|
|||
Para blcks -> pushViaConstructor "Para" blcks
|
||||
Plain blcks -> pushViaConstructor "Plain" blcks
|
||||
RawBlock f cs -> pushViaConstructor "RawBlock" f cs
|
||||
Table capt aligns widths headers rows ->
|
||||
pushViaConstructor "Table" capt aligns widths headers rows
|
||||
Table _ blkCapt specs _ thead tbody tfoot ->
|
||||
let (capt, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
in pushViaConstructor "Table" capt aligns widths headers rows
|
||||
|
||||
-- | Return the value at the given index as block if possible.
|
||||
peekBlock :: StackIndex -> Lua Block
|
||||
|
@ -192,7 +194,13 @@ peekBlock idx = defineHowTo "get Block value" $ do
|
|||
"Plain" -> Plain <$> elementContent
|
||||
"RawBlock" -> uncurry RawBlock <$> elementContent
|
||||
"Table" -> (\(capt, aligns, widths, headers, body) ->
|
||||
Table capt aligns widths headers body)
|
||||
Table nullAttr
|
||||
(Caption Nothing $ maybePara capt)
|
||||
(zip aligns (map strictPos widths))
|
||||
0
|
||||
[toRow headers]
|
||||
(map toRow body)
|
||||
[])
|
||||
<$> elementContent
|
||||
_ -> Lua.throwException ("Unknown block type: " <> tag)
|
||||
where
|
||||
|
@ -200,6 +208,11 @@ peekBlock idx = defineHowTo "get Block value" $ do
|
|||
elementContent :: Peekable a => Lua a
|
||||
elementContent = LuaUtil.rawField idx "c"
|
||||
|
||||
strictPos w = if w > 0 then Just w else Nothing
|
||||
maybePara [] = []
|
||||
maybePara x = [Para x]
|
||||
toRow = Row nullAttr . map (\blk -> Cell nullAttr Nothing 1 1 blk)
|
||||
|
||||
-- | Push an inline element to the top of the lua stack.
|
||||
pushInline :: Inline -> Lua ()
|
||||
pushInline = \case
|
||||
|
|
|
@ -55,6 +55,18 @@ instance Walkable (SingletonsList Inline) Block where
|
|||
walkM = walkBlockM
|
||||
query = queryBlock
|
||||
|
||||
instance Walkable (SingletonsList Inline) Row where
|
||||
walkM = walkRowM
|
||||
query = queryRow
|
||||
|
||||
instance Walkable (SingletonsList Inline) Caption where
|
||||
walkM = walkCaptionM
|
||||
query = queryCaption
|
||||
|
||||
instance Walkable (SingletonsList Inline) Cell where
|
||||
walkM = walkCellM
|
||||
query = queryCell
|
||||
|
||||
instance Walkable (SingletonsList Inline) MetaValue where
|
||||
walkM = walkMetaValueM
|
||||
query = queryMetaValue
|
||||
|
@ -86,6 +98,18 @@ instance Walkable (SingletonsList Block) Block where
|
|||
walkM = walkBlockM
|
||||
query = queryBlock
|
||||
|
||||
instance Walkable (SingletonsList Block) Row where
|
||||
walkM = walkRowM
|
||||
query = queryRow
|
||||
|
||||
instance Walkable (SingletonsList Block) Caption where
|
||||
walkM = walkCaptionM
|
||||
query = queryCaption
|
||||
|
||||
instance Walkable (SingletonsList Block) Cell where
|
||||
walkM = walkCellM
|
||||
query = queryCell
|
||||
|
||||
instance Walkable (SingletonsList Block) MetaValue where
|
||||
walkM = walkMetaValueM
|
||||
query = queryMetaValue
|
||||
|
|
|
@ -925,7 +925,11 @@ 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 widths) <$> heads <*> rows
|
||||
return $ B.table mempty (zip aligns (map fromWidth widths)) <$> heads <*> rows
|
||||
where
|
||||
fromWidth n
|
||||
| n > 0 = Just n
|
||||
| otherwise = Nothing
|
||||
|
||||
type TableComponents mf = ([Alignment], [Double], mf [Blocks], mf [[Blocks]])
|
||||
|
||||
|
|
|
@ -37,6 +37,6 @@ readCSV _opts s =
|
|||
hdrs = map toplain r
|
||||
rows = map (map toplain) rs
|
||||
aligns = replicate numcols AlignDefault
|
||||
widths = replicate numcols 0
|
||||
widths = replicate numcols Nothing
|
||||
Right [] -> return $ B.doc mempty
|
||||
Left e -> throwError $ PandocParsecError s e
|
||||
|
|
|
@ -111,31 +111,33 @@ addBlock opts (Node _ (LIST listAttrs) nodes) =
|
|||
PAREN_DELIM -> OneParen
|
||||
exts = readerExtensions opts
|
||||
addBlock opts (Node _ (TABLE alignments) nodes) =
|
||||
(Table [] aligns widths headers rows :)
|
||||
(Table nullAttr (Caption Nothing []) (zip aligns widths) 0 headers rows [] :)
|
||||
where aligns = map fromTableCellAlignment alignments
|
||||
fromTableCellAlignment NoAlignment = AlignDefault
|
||||
fromTableCellAlignment LeftAligned = AlignLeft
|
||||
fromTableCellAlignment RightAligned = AlignRight
|
||||
fromTableCellAlignment CenterAligned = AlignCenter
|
||||
widths = replicate numcols 0.0
|
||||
widths = replicate numcols Nothing
|
||||
numcols = if null rows'
|
||||
then 0
|
||||
else maximum $ map length rows'
|
||||
else maximum $ map rowLength rows'
|
||||
rows' = map toRow $ filter isRow nodes
|
||||
(headers, rows) = case rows' of
|
||||
(h:rs) -> (h, rs)
|
||||
(h:rs) -> ([h], rs)
|
||||
[] -> ([], [])
|
||||
isRow (Node _ TABLE_ROW _) = True
|
||||
isRow _ = False
|
||||
isCell (Node _ TABLE_CELL _) = True
|
||||
isCell _ = False
|
||||
toRow (Node _ TABLE_ROW ns) = map toCell $ filter isCell ns
|
||||
toRow (Node _ TABLE_ROW ns) = Row nullAttr $ map toCell $ filter isCell ns
|
||||
toRow (Node _ t _) = error $ "toRow encountered non-row " ++ show t
|
||||
toCell (Node _ TABLE_CELL []) = []
|
||||
toCell (Node _ TABLE_CELL []) = fromSimpleCell []
|
||||
toCell (Node _ TABLE_CELL (n:ns))
|
||||
| isBlockNode n = addBlocks opts (n:ns)
|
||||
| otherwise = [Plain (addInlines opts (n:ns))]
|
||||
| isBlockNode n = fromSimpleCell $ addBlocks opts (n:ns)
|
||||
| otherwise = fromSimpleCell [Plain (addInlines opts (n:ns))]
|
||||
toCell (Node _ t _) = error $ "toCell encountered non-cell " ++ show t
|
||||
fromSimpleCell = Cell nullAttr Nothing 1 1
|
||||
rowLength (Row _ body) = length body -- all cells are 1×1
|
||||
addBlock _ (Node _ TABLE_ROW _) = id -- handled in TABLE
|
||||
addBlock _ (Node _ TABLE_CELL _) = id -- handled in TABLE
|
||||
addBlock _ _ = id
|
||||
|
|
|
@ -676,10 +676,10 @@ getMediaobject e = do
|
|||
Just z -> mconcat <$>
|
||||
mapM parseInline (elContent z)
|
||||
figTitle <- gets dbFigureTitle
|
||||
let (caption, title) = if isNull figTitle
|
||||
then (getCaption e, "")
|
||||
else (return figTitle, "fig:")
|
||||
fmap (imageWith attr imageUrl title) caption
|
||||
let (capt, title) = if isNull figTitle
|
||||
then (getCaption e, "")
|
||||
else (return figTitle, "fig:")
|
||||
fmap (imageWith attr imageUrl title) capt
|
||||
|
||||
getBlocks :: PandocMonad m => Element -> DB m Blocks
|
||||
getBlocks e = mconcat <$>
|
||||
|
@ -844,9 +844,9 @@ parseBlock (Elem e) =
|
|||
return (mconcat $ intersperse (str "; ") terms', items')
|
||||
parseTable = do
|
||||
let isCaption x = named "title" x || named "caption" x
|
||||
caption <- case filterChild isCaption e of
|
||||
Just t -> getInlines t
|
||||
Nothing -> return mempty
|
||||
capt <- case filterChild isCaption e of
|
||||
Just t -> getInlines t
|
||||
Nothing -> return mempty
|
||||
let e' = fromMaybe e $ filterChild (named "tgroup") e
|
||||
let isColspec x = named "colspec" x || named "col" x
|
||||
let colspecs = case filterChild (named "colgroup") e' of
|
||||
|
@ -868,12 +868,12 @@ parseBlock (Elem e) =
|
|||
Just "right" -> AlignRight
|
||||
Just "center" -> AlignCenter
|
||||
_ -> AlignDefault
|
||||
let toWidth c = case findAttr (unqual "colwidth") c of
|
||||
Just w -> fromMaybe 0
|
||||
$ safeRead $ "0" <> T.filter (\x ->
|
||||
let toWidth c = do
|
||||
w <- findAttr (unqual "colwidth") c
|
||||
n <- safeRead $ "0" <> T.filter (\x ->
|
||||
(x >= '0' && x <= '9')
|
||||
|| x == '.') (T.pack w)
|
||||
Nothing -> 0 :: Double
|
||||
if n > 0 then Just n else Nothing
|
||||
let numrows = case bodyrows of
|
||||
[] -> 0
|
||||
xs -> maximum $ map length xs
|
||||
|
@ -881,16 +881,16 @@ parseBlock (Elem e) =
|
|||
[] -> replicate numrows AlignDefault
|
||||
cs -> map toAlignment cs
|
||||
let widths = case colspecs of
|
||||
[] -> replicate numrows 0
|
||||
cs -> let ws = map toWidth cs
|
||||
tot = sum ws
|
||||
in if all (> 0) ws
|
||||
then map (/ tot) ws
|
||||
else replicate numrows 0
|
||||
[] -> replicate numrows Nothing
|
||||
cs -> let ws = map toWidth cs
|
||||
in case sequence ws of
|
||||
Just ws' -> let tot = sum ws'
|
||||
in Just . (/ tot) <$> ws'
|
||||
Nothing -> replicate numrows Nothing
|
||||
let headrows' = if null headrows
|
||||
then replicate numrows mempty
|
||||
else headrows
|
||||
return $ table caption (zip aligns widths)
|
||||
return $ table capt (zip aligns widths)
|
||||
headrows' bodyrows
|
||||
isEntry x = named "entry" x || named "td" x || named "th" x
|
||||
parseRow = mapM (parseMixed plain . elContent) . filterChildren isEntry
|
||||
|
|
|
@ -77,7 +77,7 @@ import Text.Pandoc.MediaBag (MediaBag)
|
|||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Readers.Docx.Combine
|
||||
import Text.Pandoc.Readers.Docx.Lists
|
||||
import Text.Pandoc.Readers.Docx.Parse
|
||||
import Text.Pandoc.Readers.Docx.Parse as Docx
|
||||
import Text.Pandoc.Shared
|
||||
import Text.Pandoc.Walk
|
||||
import Text.TeXMath (writeTeX)
|
||||
|
@ -494,13 +494,13 @@ singleParaToPlain blks
|
|||
singleton $ Plain ils
|
||||
singleParaToPlain blks = blks
|
||||
|
||||
cellToBlocks :: PandocMonad m => Cell -> DocxContext m Blocks
|
||||
cellToBlocks (Cell bps) = do
|
||||
cellToBlocks :: PandocMonad m => Docx.Cell -> DocxContext m Blocks
|
||||
cellToBlocks (Docx.Cell bps) = do
|
||||
blks <- smushBlocks <$> mapM bodyPartToBlocks bps
|
||||
return $ fromList $ blocksToDefinitions $ blocksToBullets $ toList blks
|
||||
|
||||
rowToBlocksList :: PandocMonad m => Row -> DocxContext m [Blocks]
|
||||
rowToBlocksList (Row cells) = do
|
||||
rowToBlocksList :: PandocMonad m => Docx.Row -> DocxContext m [Blocks]
|
||||
rowToBlocksList (Docx.Row cells) = do
|
||||
blksList <- mapM cellToBlocks cells
|
||||
return $ map singleParaToPlain blksList
|
||||
|
||||
|
@ -645,7 +645,7 @@ bodyPartToBlocks (ListItem pPr _ _ _ parparts) =
|
|||
bodyPartToBlocks (Tbl _ _ _ []) =
|
||||
return $ para mempty
|
||||
bodyPartToBlocks (Tbl cap _ look parts@(r:rs)) = do
|
||||
let caption = text cap
|
||||
let cap' = text cap
|
||||
(hdr, rows) = case firstRowFormatting look of
|
||||
True | null rs -> (Nothing, [r])
|
||||
| otherwise -> (Just r, rs)
|
||||
|
@ -659,8 +659,8 @@ bodyPartToBlocks (Tbl cap _ look parts@(r:rs)) = do
|
|||
-- https://github.com/jgm/pandoc/pull/4361#issuecomment-365416155
|
||||
nonEmpty [] = Nothing
|
||||
nonEmpty l = Just l
|
||||
rowLength :: Row -> Int
|
||||
rowLength (Row c) = length c
|
||||
rowLength :: Docx.Row -> Int
|
||||
rowLength (Docx.Row c) = length c
|
||||
|
||||
-- pad cells. New Text.Pandoc.Builder will do that for us,
|
||||
-- so this is for compatibility while we switch over.
|
||||
|
@ -676,9 +676,9 @@ bodyPartToBlocks (Tbl cap _ look parts@(r:rs)) = do
|
|||
-- so should be possible. Alignment might be more difficult,
|
||||
-- since there doesn't seem to be a column entity in docx.
|
||||
let alignments = replicate width AlignDefault
|
||||
widths = replicate width 0 :: [Double]
|
||||
widths = replicate width Nothing
|
||||
|
||||
return $ table caption (zip alignments widths) hdrCells cells'
|
||||
return $ table cap' (zip alignments widths) hdrCells cells'
|
||||
bodyPartToBlocks (OMathPara e) =
|
||||
return $ para $ displayMath (writeTeX e)
|
||||
|
||||
|
|
|
@ -470,7 +470,7 @@ table = do
|
|||
let (headerRow, body) = if firstSeparator == '^'
|
||||
then (head rows, tail rows)
|
||||
else ([], rows)
|
||||
let attrs = (AlignDefault, 0.0) <$ transpose rows
|
||||
let attrs = (AlignDefault, Nothing) <$ transpose rows
|
||||
pure $ B.table mempty attrs headerRow body
|
||||
|
||||
tableRows :: PandocMonad m => DWParser m [[B.Blocks]]
|
||||
|
|
|
@ -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,
|
||||
onlySimpleTableCells, safeRead, underlineSpan, tshow)
|
||||
onlySimpleCellBodies, 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 = onlySimpleTableCells $ fmap B.toList <$> head':rows'''
|
||||
let isSimple = onlySimpleCellBodies $ fmap B.toList <$> head':rows'''
|
||||
let cols = if null head'
|
||||
then maximum (map length rows''')
|
||||
else length head'
|
||||
|
@ -513,12 +513,12 @@ pTable = try $ do
|
|||
_ -> replicate cols AlignDefault
|
||||
let widths = if null widths'
|
||||
then if isSimple
|
||||
then replicate cols 0
|
||||
else replicate cols (1.0 / fromIntegral cols)
|
||||
then replicate cols Nothing
|
||||
else replicate cols (Just (1.0 / fromIntegral cols))
|
||||
else widths'
|
||||
return $ B.table caption (zip aligns widths) head' rows
|
||||
|
||||
pCol :: PandocMonad m => TagParser m Double
|
||||
pCol :: PandocMonad m => TagParser m (Maybe Double)
|
||||
pCol = try $ do
|
||||
TagOpen _ attribs' <- pSatisfy (matchTagOpen "col" [])
|
||||
let attribs = toStringAttr attribs'
|
||||
|
@ -535,10 +535,10 @@ pCol = try $ do
|
|||
fromMaybe 0.0 $ safeRead xs
|
||||
_ -> 0.0
|
||||
if width > 0.0
|
||||
then return $ width / 100.0
|
||||
else return 0.0
|
||||
then return $ Just $ width / 100.0
|
||||
else return Nothing
|
||||
|
||||
pColgroup :: PandocMonad m => TagParser m [Double]
|
||||
pColgroup :: PandocMonad m => TagParser m [Maybe Double]
|
||||
pColgroup = try $ do
|
||||
pSatisfy (matchTagOpen "colgroup" [])
|
||||
skipMany pBlank
|
||||
|
|
|
@ -91,7 +91,7 @@ docHToBlocks d' =
|
|||
else (toCells (head headerRows),
|
||||
map toCells (tail headerRows ++ bodyRows))
|
||||
colspecs = replicate (maximum (map length body))
|
||||
(AlignDefault, 0.0)
|
||||
(AlignDefault, Nothing)
|
||||
in B.table mempty colspecs header body
|
||||
|
||||
where inlineFallback = B.plain $ docHToInlines False d'
|
||||
|
|
|
@ -69,7 +69,7 @@ notebookToPandoc opts notebook = do
|
|||
return $ Pandoc (Meta $ M.insert "jupyter" (MetaMap m) mempty) blocks
|
||||
|
||||
cellToBlocks :: PandocMonad m
|
||||
=> ReaderOptions -> Text -> Cell a -> m B.Blocks
|
||||
=> ReaderOptions -> Text -> Ipynb.Cell a -> m B.Blocks
|
||||
cellToBlocks opts lang c = do
|
||||
let Source ts = cellSource c
|
||||
let source = mconcat ts
|
||||
|
|
|
@ -134,14 +134,14 @@ getGraphic :: PandocMonad m
|
|||
=> Maybe (Inlines, Text) -> Element -> JATS m Inlines
|
||||
getGraphic mbfigdata e = do
|
||||
let atVal a = attrValue a e
|
||||
(ident, title, caption) =
|
||||
(ident, title, capt) =
|
||||
case mbfigdata of
|
||||
Just (capt, i) -> (i, "fig:" <> atVal "title", capt)
|
||||
Just (capt', i) -> (i, "fig:" <> atVal "title", capt')
|
||||
Nothing -> (atVal "id", atVal "title",
|
||||
text (atVal "alt-text"))
|
||||
attr = (ident, T.words $ atVal "role", [])
|
||||
imageUrl = atVal "href"
|
||||
return $ imageWith attr imageUrl title caption
|
||||
return $ imageWith attr imageUrl title capt
|
||||
|
||||
getBlocks :: PandocMonad m => Element -> JATS m Blocks
|
||||
getBlocks e = mconcat <$>
|
||||
|
@ -230,20 +230,20 @@ parseBlock (Elem e) =
|
|||
-- implicit figure. otherwise, we emit a div with the contents
|
||||
case filterChildren (named "graphic") e of
|
||||
[g] -> do
|
||||
caption <- case filterChild (named "caption") e of
|
||||
Just t -> mconcat .
|
||||
intersperse linebreak <$>
|
||||
mapM getInlines
|
||||
(filterChildren (const True) t)
|
||||
Nothing -> return mempty
|
||||
img <- getGraphic (Just (caption, attrValue "id" e)) g
|
||||
capt <- case filterChild (named "caption") e of
|
||||
Just t -> mconcat .
|
||||
intersperse linebreak <$>
|
||||
mapM getInlines
|
||||
(filterChildren (const True) t)
|
||||
Nothing -> return mempty
|
||||
img <- getGraphic (Just (capt, attrValue "id" e)) g
|
||||
return $ para img
|
||||
_ -> divWith (attrValue "id" e, ["fig"], []) <$> getBlocks e
|
||||
parseTable = do
|
||||
let isCaption x = named "title" x || named "caption" x
|
||||
caption <- case filterChild isCaption e of
|
||||
Just t -> getInlines t
|
||||
Nothing -> return mempty
|
||||
capt <- case filterChild isCaption e of
|
||||
Just t -> getInlines t
|
||||
Nothing -> return mempty
|
||||
let e' = fromMaybe e $ filterChild (named "tgroup") e
|
||||
let isColspec x = named "colspec" x || named "col" x
|
||||
let colspecs = case filterChild (named "colgroup") e' of
|
||||
|
@ -265,26 +265,25 @@ parseBlock (Elem e) =
|
|||
Just "right" -> AlignRight
|
||||
Just "center" -> AlignCenter
|
||||
_ -> AlignDefault
|
||||
let toWidth c = case findAttrText (unqual "colwidth") c of
|
||||
Just w -> fromMaybe 0
|
||||
$ safeRead $ "0" <> T.filter (\x ->
|
||||
isDigit x || x == '.') w
|
||||
Nothing -> 0 :: Double
|
||||
let toWidth c = do
|
||||
w <- findAttrText (unqual "colwidth") c
|
||||
n <- safeRead $ "0" <> T.filter (\x -> isDigit x || x == '.') w
|
||||
if n > 0 then Just n else Nothing
|
||||
let numrows = foldl' max 0 $ map length bodyrows
|
||||
let aligns = case colspecs of
|
||||
[] -> replicate numrows AlignDefault
|
||||
cs -> map toAlignment cs
|
||||
let widths = case colspecs of
|
||||
[] -> replicate numrows 0
|
||||
cs -> let ws = map toWidth cs
|
||||
tot = sum ws
|
||||
in if all (> 0) ws
|
||||
then map (/ tot) ws
|
||||
else replicate numrows 0
|
||||
[] -> replicate numrows Nothing
|
||||
cs -> let ws = map toWidth cs
|
||||
in case sequence ws of
|
||||
Just ws' -> let tot = sum ws'
|
||||
in Just . (/ tot) <$> ws'
|
||||
Nothing -> replicate numrows Nothing
|
||||
let headrows' = if null headrows
|
||||
then replicate numrows mempty
|
||||
else headrows
|
||||
return $ table caption (zip aligns widths)
|
||||
return $ table capt (zip aligns widths)
|
||||
headrows' bodyrows
|
||||
isEntry x = named "entry" x || named "td" x || named "th" x
|
||||
parseRow = mapM (parseMixed plain . elContent) . filterChildren isEntry
|
||||
|
|
|
@ -2268,7 +2268,7 @@ splitWordTok = do
|
|||
setInput $ map (Tok spos Symbol . T.singleton) (T.unpack t) <> rest
|
||||
_ -> return ()
|
||||
|
||||
parseAligns :: PandocMonad m => LP m [(Alignment, Double, ([Tok], [Tok]))]
|
||||
parseAligns :: PandocMonad m => LP m [(Alignment, Maybe Double, ([Tok], [Tok]))]
|
||||
parseAligns = try $ do
|
||||
let maybeBar = skipMany
|
||||
(try $ sp *> (() <$ symbol '|' <|> () <$ (symbol '@' >> braced)))
|
||||
|
@ -2289,17 +2289,15 @@ parseAligns = try $ do
|
|||
ds <- trim . untokenize <$> manyTill anyTok (controlSeq "linewidth")
|
||||
spaces
|
||||
symbol '}'
|
||||
case safeRead ds of
|
||||
Just w -> return w
|
||||
Nothing -> return 0.0
|
||||
return $ safeRead ds
|
||||
let alignSpec = do
|
||||
pref <- option [] alignPrefix
|
||||
spaces
|
||||
al <- alignChar
|
||||
width <- colWidth <|> option 0.0 (do s <- untokenize <$> braced
|
||||
pos <- getPosition
|
||||
report $ SkippedContent s pos
|
||||
return 0.0)
|
||||
width <- colWidth <|> option Nothing (do s <- untokenize <$> braced
|
||||
pos <- getPosition
|
||||
report $ SkippedContent s pos
|
||||
return Nothing)
|
||||
spaces
|
||||
suff <- option [] alignSuffix
|
||||
return (al, width, (pref, suff))
|
||||
|
@ -2399,11 +2397,11 @@ simpTable envname hasWidthParameter = try $ do
|
|||
|
||||
addTableCaption :: PandocMonad m => Blocks -> LP m Blocks
|
||||
addTableCaption = walkM go
|
||||
where go (Table c als ws hs rs) = do
|
||||
where go (Table attr c spec rhs th tb tf) = do
|
||||
st <- getState
|
||||
let mblabel = sLastLabel st
|
||||
capt <- case (sCaption st, mblabel) of
|
||||
(Just ils, Nothing) -> return $ toList ils
|
||||
(Just ils, Nothing) -> return $ Caption Nothing (mcap ils)
|
||||
(Just ils, Just lab) -> do
|
||||
num <- getNextNumber sLastTableNum
|
||||
setState
|
||||
|
@ -2411,11 +2409,14 @@ addTableCaption = walkM go
|
|||
, sLabels = M.insert lab
|
||||
[Str (renderDottedNum num)]
|
||||
(sLabels st) }
|
||||
return $ toList ils -- add number??
|
||||
return $ Caption Nothing (mcap ils) -- add number??
|
||||
(Nothing, _) -> return c
|
||||
return $ maybe id (\ident -> Div (ident, [], []) . (:[])) mblabel $
|
||||
Table capt als ws hs rs
|
||||
Table attr capt spec rhs th tb tf
|
||||
go x = return x
|
||||
mcap ils
|
||||
| isNull ils = []
|
||||
| otherwise = [Para $ toList ils]
|
||||
|
||||
|
||||
block :: PandocMonad m => LP m Blocks
|
||||
|
|
|
@ -107,9 +107,9 @@ parseTable = do
|
|||
bodyRows <- mapM (mapM parseTableCell . snd) bodyRows'
|
||||
isPlainTable <- tableCellsPlain <$> getState
|
||||
let widths = if isPlainTable
|
||||
then repeat 0.0
|
||||
else repeat ((1.0 / fromIntegral (length alignments))
|
||||
:: Double)
|
||||
then repeat Nothing
|
||||
else repeat (Just (1.0 / fromIntegral (length alignments))
|
||||
:: Maybe Double)
|
||||
return $ B.table mempty (zip alignments widths)
|
||||
headerRow bodyRows) <|> fallback pos
|
||||
[] -> fallback pos
|
||||
|
@ -160,7 +160,6 @@ parseTable = do
|
|||
'r' -> Just AlignRight
|
||||
_ -> Nothing
|
||||
|
||||
|
||||
parseNewParagraph :: PandocMonad m => ManParser m Blocks
|
||||
parseNewParagraph = do
|
||||
mmacro "P" <|> mmacro "PP" <|> mmacro "LP" <|> memptyLine
|
||||
|
|
|
@ -1417,11 +1417,14 @@ table = try $ do
|
|||
let widths' = if totalWidth < 1
|
||||
then widths
|
||||
else map (/ totalWidth) widths
|
||||
let strictPos w
|
||||
| w > 0 = Just w
|
||||
| otherwise = Nothing
|
||||
return $ do
|
||||
caption' <- caption
|
||||
heads' <- heads
|
||||
lns' <- lns
|
||||
return $ B.table caption' (zip aligns widths') heads' lns'
|
||||
return $ B.table caption' (zip aligns (strictPos <$> widths')) heads' lns'
|
||||
|
||||
--
|
||||
-- inline
|
||||
|
|
|
@ -221,9 +221,9 @@ table = do
|
|||
let restwidth = tableWidth - sum widths
|
||||
let zerocols = length $ filter (==0.0) widths
|
||||
let defaultwidth = if zerocols == 0 || zerocols == length widths
|
||||
then 0.0
|
||||
else restwidth / fromIntegral zerocols
|
||||
let widths' = map (\w -> if w == 0 then defaultwidth else w) widths
|
||||
then Nothing
|
||||
else Just $ restwidth / fromIntegral zerocols
|
||||
let widths' = map (\w -> if w == 0 then defaultwidth else Just w) widths
|
||||
let cellspecs = zip (map fst cellspecs') widths'
|
||||
rows' <- many $ try $ rowsep *> (map snd <$> tableRow)
|
||||
optional blanklines
|
||||
|
|
|
@ -646,7 +646,7 @@ data MuseTableElement = MuseHeaderRow [Blocks]
|
|||
museToPandocTable :: MuseTable -> Blocks
|
||||
museToPandocTable (MuseTable caption headers body footers) =
|
||||
B.table caption attrs headRow (rows ++ body ++ footers)
|
||||
where attrs = (AlignDefault, 0.0) <$ transpose (headers ++ body ++ footers)
|
||||
where attrs = (AlignDefault, Nothing) <$ transpose (headers ++ body ++ footers)
|
||||
(headRow, rows) = fromMaybe ([], []) $ uncons headers
|
||||
|
||||
museAppendElement :: MuseTableElement
|
||||
|
@ -694,7 +694,7 @@ museGridTable = try $ do
|
|||
indices <- museGridTableHeader
|
||||
fmap rowsToTable . sequence <$> many1 (museGridTableRow indent indices)
|
||||
where rowsToTable rows = B.table mempty attrs [] rows
|
||||
where attrs = (AlignDefault, 0.0) <$ transpose rows
|
||||
where attrs = (AlignDefault, Nothing) <$ transpose rows
|
||||
|
||||
-- | Parse a table.
|
||||
table :: PandocMonad m => MuseParser m (F Blocks)
|
||||
|
|
|
@ -921,8 +921,8 @@ post_process (Pandoc m blocks) =
|
|||
Pandoc m (post_process' blocks)
|
||||
|
||||
post_process' :: [Block] -> [Block]
|
||||
post_process' (Table _ a w h r : Div ("", ["caption"], _) [Para inlines] : xs) =
|
||||
Table inlines a w h r : post_process' xs
|
||||
post_process' (Table attr _ specs rhs th tb tf : Div ("", ["caption"], _) blks : xs)
|
||||
= Table attr (Caption Nothing blks) specs rhs th tb tf : post_process' xs
|
||||
post_process' bs = bs
|
||||
|
||||
read_body :: OdtReader _x (Pandoc, MediaBag)
|
||||
|
|
|
@ -629,13 +629,13 @@ orgToPandocTable (OrgTable colProps heads lns) caption =
|
|||
else Nothing
|
||||
in B.table caption (map (convertColProp totalWidth) colProps) heads lns
|
||||
where
|
||||
convertColProp :: Maybe Int -> ColumnProperty -> (Alignment, Double)
|
||||
convertColProp :: Maybe Int -> ColumnProperty -> (Alignment, Maybe Double)
|
||||
convertColProp totalWidth colProp =
|
||||
let
|
||||
align' = fromMaybe AlignDefault $ columnAlignment colProp
|
||||
width' = fromMaybe 0 $ (\w t -> (fromIntegral w / fromIntegral t))
|
||||
<$> columnRelWidth colProp
|
||||
<*> totalWidth
|
||||
width' = (\w t -> (fromIntegral w / fromIntegral t))
|
||||
<$> columnRelWidth colProp
|
||||
<*> totalWidth
|
||||
in (align', width')
|
||||
|
||||
tableRows :: PandocMonad m => OrgParser m [OrgTableRow]
|
||||
|
@ -658,16 +658,16 @@ tableAlignRow = try $ do
|
|||
return $ OrgAlignRow colProps
|
||||
|
||||
columnPropertyCell :: Monad m => OrgParser m ColumnProperty
|
||||
columnPropertyCell = emptyCell <|> propCell <?> "alignment info"
|
||||
columnPropertyCell = emptyOrgCell <|> propCell <?> "alignment info"
|
||||
where
|
||||
emptyCell = ColumnProperty Nothing Nothing <$ try (skipSpaces *> endOfCell)
|
||||
emptyOrgCell = ColumnProperty Nothing Nothing <$ try (skipSpaces *> endOfCell)
|
||||
propCell = try $ ColumnProperty
|
||||
<$> (skipSpaces
|
||||
*> char '<'
|
||||
*> optionMaybe tableAlignFromChar)
|
||||
<*> (optionMaybe (many1Char digit >>= safeRead)
|
||||
<* char '>'
|
||||
<* emptyCell)
|
||||
<* emptyOrgCell)
|
||||
|
||||
tableAlignFromChar :: Monad m => OrgParser m Alignment
|
||||
tableAlignFromChar = try $
|
||||
|
|
|
@ -770,24 +770,37 @@ tableDirective :: PandocMonad m
|
|||
tableDirective top fields body = do
|
||||
bs <- parseFromString' parseBlocks body
|
||||
case B.toList bs of
|
||||
[Table _ aligns' widths' header' rows'] -> do
|
||||
[Table attr _ tspecs' rhs thead tbody tfoot] -> do
|
||||
let (aligns', widths') = unzip tspecs'
|
||||
title <- parseFromString' (trimInlines . mconcat <$> many inline) top
|
||||
columns <- getOption readerColumns
|
||||
let numOfCols = length header'
|
||||
let numOfCols = case thead of
|
||||
[] -> 0
|
||||
(r:_) -> rowLength r
|
||||
let normWidths ws =
|
||||
map (/ max 1.0 (fromIntegral (columns - numOfCols))) ws
|
||||
strictPos . (/ max 1.0 (fromIntegral (columns - numOfCols))) <$> ws
|
||||
let widths = case trim <$> lookup "widths" fields of
|
||||
Just "auto" -> replicate numOfCols 0.0
|
||||
Just "auto" -> replicate numOfCols Nothing
|
||||
Just "grid" -> widths'
|
||||
Just specs -> normWidths
|
||||
$ map (fromMaybe (0 :: Double) . safeRead)
|
||||
$ splitTextBy (`elem` (" ," :: String)) specs
|
||||
Nothing -> widths'
|
||||
-- align is not applicable since we can't represent whole table align
|
||||
return $ B.singleton $ Table (B.toList title)
|
||||
aligns' widths header' rows'
|
||||
let tspecs = zip aligns' widths
|
||||
return $ B.singleton $ Table attr (Caption Nothing (mpara title))
|
||||
tspecs rhs thead tbody tfoot
|
||||
_ -> return mempty
|
||||
|
||||
where
|
||||
-- only valid on the very first row of a table section
|
||||
rowLength (Row _ rb) = sum $ cellLength <$> rb
|
||||
cellLength (Cell _ _ _ w _) = if w < 0 then 0 else w
|
||||
strictPos w
|
||||
| w > 0 = Just w
|
||||
| otherwise = Nothing
|
||||
mpara t
|
||||
| B.isNull t = []
|
||||
| otherwise = [Para $ B.toList t]
|
||||
|
||||
-- TODO: :stub-columns:.
|
||||
-- Only the first row becomes the header even if header-rows: > 1,
|
||||
|
@ -808,10 +821,10 @@ listTableDirective top fields body = do
|
|||
else ([], rows, length x)
|
||||
_ -> ([],[],0)
|
||||
widths = case trim <$> lookup "widths" fields of
|
||||
Just "auto" -> replicate numOfCols 0
|
||||
Just "auto" -> replicate numOfCols Nothing
|
||||
Just specs -> normWidths $ map (fromMaybe (0 :: Double) . safeRead) $
|
||||
splitTextBy (`elem` (" ," :: String)) specs
|
||||
_ -> replicate numOfCols 0
|
||||
_ -> replicate numOfCols Nothing
|
||||
return $ B.table title
|
||||
(zip (replicate numOfCols AlignDefault) widths)
|
||||
headerRow
|
||||
|
@ -820,7 +833,10 @@ listTableDirective top fields body = do
|
|||
takeRows _ = []
|
||||
takeCells [BulletList cells] = map B.fromList cells
|
||||
takeCells _ = []
|
||||
normWidths ws = map (/ max 1 (sum ws)) ws
|
||||
normWidths ws = strictPos . (/ max 1 (sum ws)) <$> ws
|
||||
strictPos w
|
||||
| w > 0 = Just w
|
||||
| otherwise = Nothing
|
||||
|
||||
csvTableDirective :: PandocMonad m
|
||||
=> Text -> [(Text, Text)] -> Text
|
||||
|
@ -873,14 +889,17 @@ csvTableDirective top fields rawcsv = do
|
|||
else ([], rows, length x)
|
||||
_ -> ([],[],0)
|
||||
title <- parseFromString' (trimInlines . mconcat <$> many inline) top
|
||||
let normWidths ws = map (/ max 1 (sum ws)) ws
|
||||
let strictPos w
|
||||
| w > 0 = Just w
|
||||
| otherwise = Nothing
|
||||
let normWidths ws = strictPos . (/ max 1 (sum ws)) <$> ws
|
||||
let widths =
|
||||
case trim <$> lookup "widths" fields of
|
||||
Just "auto" -> replicate numOfCols 0
|
||||
Just "auto" -> replicate numOfCols Nothing
|
||||
Just specs -> normWidths
|
||||
$ map (fromMaybe (0 :: Double) . safeRead)
|
||||
$ splitTextBy (`elem` (" ," :: String)) specs
|
||||
_ -> replicate numOfCols 0
|
||||
_ -> replicate numOfCols Nothing
|
||||
return $ B.table title
|
||||
(zip (replicate numOfCols AlignDefault) widths)
|
||||
headerRow
|
||||
|
@ -1293,13 +1312,14 @@ simpleTable headless = do
|
|||
sep simpleTableFooter
|
||||
-- Simple tables get 0s for relative column widths (i.e., use default)
|
||||
case B.toList tbl of
|
||||
[Table c a _w h l] -> return $ B.singleton $
|
||||
Table c a (replicate (length a) 0) h l
|
||||
[Table attr cap spec rhs th tb tf] -> return $ B.singleton $
|
||||
Table attr cap (rewidth spec) rhs th tb tf
|
||||
_ ->
|
||||
throwError $ PandocShouldNeverHappenError
|
||||
"tableWith returned something unexpected"
|
||||
where
|
||||
sep = return () -- optional (simpleTableSep '-')
|
||||
rewidth = fmap $ fmap $ const Nothing
|
||||
|
||||
gridTable :: PandocMonad m
|
||||
=> Bool -- ^ Headerless table
|
||||
|
|
|
@ -229,11 +229,11 @@ table = try $ do
|
|||
where
|
||||
buildTable caption rows (aligns, heads)
|
||||
= B.table caption aligns heads rows
|
||||
align rows = replicate (columCount rows) (AlignDefault, 0)
|
||||
align rows = replicate (columCount rows) (AlignDefault, Nothing)
|
||||
columns rows = replicate (columCount rows) mempty
|
||||
columCount rows = length $ head rows
|
||||
|
||||
tableParseHeader :: PandocMonad m => TWParser m ((Alignment, Double), B.Blocks)
|
||||
tableParseHeader :: PandocMonad m => TWParser m ((Alignment, Maybe Double), B.Blocks)
|
||||
tableParseHeader = try $ do
|
||||
char '|'
|
||||
leftSpaces <- length <$> many spaceChar
|
||||
|
@ -245,9 +245,9 @@ tableParseHeader = try $ do
|
|||
return (tableAlign leftSpaces rightSpaces, content)
|
||||
where
|
||||
tableAlign left right
|
||||
| left >= 2 && left == right = (AlignCenter, 0)
|
||||
| left > right = (AlignRight, 0)
|
||||
| otherwise = (AlignLeft, 0)
|
||||
| left >= 2 && left == right = (AlignCenter, Nothing)
|
||||
| left > right = (AlignRight, Nothing)
|
||||
| otherwise = (AlignLeft, Nothing)
|
||||
|
||||
tableParseRow :: PandocMonad m => TWParser m [B.Blocks]
|
||||
tableParseRow = many1Till tableParseColumn newline
|
||||
|
|
|
@ -378,7 +378,7 @@ table = try $ do
|
|||
let nbOfCols = maximum $ map length (headers:rows)
|
||||
let aligns = map minimum $ transpose $ map (map (snd . fst)) (headers:rows)
|
||||
return $ B.table caption
|
||||
(zip aligns (replicate nbOfCols 0.0))
|
||||
(zip aligns (replicate nbOfCols Nothing))
|
||||
(map snd headers)
|
||||
(map (map snd) rows)
|
||||
|
||||
|
|
|
@ -268,7 +268,7 @@ table = try $ do
|
|||
let rowsPadded = map (pad size) rows'
|
||||
let headerPadded = if null tableHeader then mempty else pad size tableHeader
|
||||
return $ B.table mempty
|
||||
(zip aligns (replicate ncolumns 0.0))
|
||||
(zip aligns (replicate ncolumns Nothing))
|
||||
headerPadded rowsPadded
|
||||
|
||||
pad :: (Monoid a) => Int -> [a] -> [a]
|
||||
|
|
|
@ -67,6 +67,7 @@ module Text.Pandoc.Shared (
|
|||
headerShift,
|
||||
stripEmptyParagraphs,
|
||||
onlySimpleTableCells,
|
||||
onlySimpleCellBodies,
|
||||
isTightList,
|
||||
taskListItemFromAscii,
|
||||
taskListItemToAscii,
|
||||
|
@ -77,6 +78,7 @@ module Text.Pandoc.Shared (
|
|||
htmlSpanLikeElements,
|
||||
splitSentences,
|
||||
filterIpynbOutput,
|
||||
toLegacyTable,
|
||||
-- * TagSoup HTML handling
|
||||
renderTags',
|
||||
-- * File handling
|
||||
|
@ -667,8 +669,18 @@ stripEmptyParagraphs = walk go
|
|||
|
||||
-- | Detect if table rows contain only cells consisting of a single
|
||||
-- paragraph that has no @LineBreak@.
|
||||
onlySimpleTableCells :: [[TableCell]] -> Bool
|
||||
onlySimpleTableCells = all isSimpleCell . concat
|
||||
|
||||
-- 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
|
||||
where
|
||||
isSimpleCell [Plain ils] = not (hasLineBreak ils)
|
||||
isSimpleCell [Para ils ] = not (hasLineBreak ils)
|
||||
|
@ -992,9 +1004,12 @@ blockToInlines (DefinitionList pairslst) =
|
|||
mconcat (map blocksToInlines' blkslst)
|
||||
blockToInlines (Header _ _ ils) = B.fromList ils
|
||||
blockToInlines HorizontalRule = mempty
|
||||
blockToInlines (Table _ _ _ headers rows) =
|
||||
blockToInlines (Table _ _ _ _ headers rows feet) =
|
||||
mconcat $ intersperse B.linebreak $
|
||||
map (mconcat . map blocksToInlines') (headers:rows)
|
||||
map (mconcat . map blocksToInlines') (plainRowBody <$> headers <> rows <> feet)
|
||||
where
|
||||
plainRowBody (Row _ body) = cellBody <$> body
|
||||
cellBody (Cell _ _ _ _ body) = body
|
||||
blockToInlines (Div _ blks) = blocksToInlines' blks
|
||||
blockToInlines Null = mempty
|
||||
|
||||
|
@ -1008,6 +1023,30 @@ blocksToInlines' = blocksToInlinesWithSep defaultBlocksSeparator
|
|||
blocksToInlines :: [Block] -> [Inline]
|
||||
blocksToInlines = B.toList . blocksToInlines'
|
||||
|
||||
-- | Convert the relevant components of a new-style table (with block
|
||||
-- caption, row headers, row and column spans, and so on) to those of
|
||||
-- an old-style table (inline caption, table head with one row, no
|
||||
-- foot, and so on).
|
||||
toLegacyTable :: Caption
|
||||
-> [ColSpec]
|
||||
-> TableHead
|
||||
-> TableBody
|
||||
-> TableFoot
|
||||
-> ([Inline], [Alignment], [Double], [[Block]], [[[Block]]])
|
||||
toLegacyTable (Caption _ cbody) specs th tb tf = (cbody', aligns, widths, th', tb')
|
||||
where
|
||||
numcols = length specs
|
||||
(aligns, mwidths) = unzip specs
|
||||
widths = map (fromMaybe 0) mwidths
|
||||
unRow (Row _ x) = map unCell x
|
||||
unCell (Cell _ _ _ _ x) = x
|
||||
cbody' = blocksToInlines cbody
|
||||
sanitise = pad mempty numcols . unRow
|
||||
pad element upTo list = take upTo (list ++ repeat element)
|
||||
(th', tb') = case th of
|
||||
(r:rs) -> (sanitise r, map sanitise $ rs <> tb <> tf)
|
||||
[] -> ([], map sanitise $ tb <> tf)
|
||||
|
||||
-- | Inline elements used to separate blocks when squashing blocks into
|
||||
-- inlines.
|
||||
defaultBlocksSeparator :: Inlines
|
||||
|
@ -1016,7 +1055,6 @@ defaultBlocksSeparator =
|
|||
-- there should be updated if this is changed.
|
||||
B.space <> B.str "¶" <> B.space
|
||||
|
||||
|
||||
--
|
||||
-- Safe read
|
||||
--
|
||||
|
|
|
@ -191,7 +191,8 @@ blockToAsciiDoc opts (BlockQuote blocks) = do
|
|||
else contents
|
||||
let bar = text "____"
|
||||
return $ bar $$ chomp contents' $$ bar <> blankline
|
||||
blockToAsciiDoc opts (Table caption aligns widths headers rows) = do
|
||||
blockToAsciiDoc opts (Table _ blkCapt specs _ thead tbody tfoot) = do
|
||||
let (caption, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
caption' <- inlineListToAsciiDoc opts caption
|
||||
let caption'' = if null caption
|
||||
then empty
|
||||
|
|
|
@ -27,7 +27,7 @@ import Text.Pandoc.Class.PandocMonad (PandocMonad)
|
|||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Shared (capitalize, isTightList,
|
||||
linesToPara, onlySimpleTableCells, taskListItemToAscii, tshow)
|
||||
linesToPara, onlySimpleTableCells, taskListItemToAscii, tshow, toLegacyTable)
|
||||
import Text.Pandoc.Templates (renderTemplate)
|
||||
import Text.Pandoc.Walk (walk, walkM)
|
||||
import Text.Pandoc.Writers.HTML (writeHtml5String, tagWithAttributes)
|
||||
|
@ -154,71 +154,72 @@ blockToNodes opts (DefinitionList items) ns =
|
|||
Plain (term ++ [LineBreak] ++ xs) : ys ++ concat zs
|
||||
dlToBullet (term, xs) =
|
||||
Para term : concat xs
|
||||
blockToNodes opts t@(Table capt aligns _widths headers rows) ns =
|
||||
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
|
||||
-- rendering TABLE nodes; (2) we can align the column sides;
|
||||
-- (3) we can render the caption as a regular paragraph.
|
||||
let capt' = node PARAGRAPH (inlinesToNodes opts capt)
|
||||
-- backslash | in code and raw:
|
||||
let fixPipe (Code attr xs) =
|
||||
Code attr (T.replace "|" "\\|" xs)
|
||||
fixPipe (RawInline format xs) =
|
||||
RawInline format (T.replace "|" "\\|" xs)
|
||||
fixPipe x = x
|
||||
let toCell [Plain ils] = T.strip
|
||||
$ nodeToCommonmark [] Nothing
|
||||
$ node (CUSTOM_INLINE mempty mempty)
|
||||
$ inlinesToNodes opts
|
||||
$ walk (fixPipe . softBreakToSpace) ils
|
||||
toCell [Para ils] = T.strip
|
||||
$ nodeToCommonmark [] Nothing
|
||||
$ node (CUSTOM_INLINE mempty mempty)
|
||||
$ inlinesToNodes opts
|
||||
$ walk (fixPipe . softBreakToSpace) ils
|
||||
toCell [] = ""
|
||||
toCell xs = error $ "toCell encountered " ++ show xs
|
||||
let separator = " | "
|
||||
let starter = "| "
|
||||
let ender = " |"
|
||||
let rawheaders = map toCell headers
|
||||
let rawrows = map (map toCell) rows
|
||||
let maximum' [] = 0
|
||||
maximum' xs = maximum xs
|
||||
let colwidths = map (maximum' . map T.length) $
|
||||
transpose (rawheaders:rawrows)
|
||||
let toHeaderLine len AlignDefault = T.replicate len "-"
|
||||
toHeaderLine len AlignLeft = ":" <>
|
||||
T.replicate (max (len - 1) 1) "-"
|
||||
toHeaderLine len AlignRight =
|
||||
T.replicate (max (len - 1) 1) "-" <> ":"
|
||||
toHeaderLine len AlignCenter = ":" <>
|
||||
T.replicate (max (len - 2) 1) (T.pack "-") <> ":"
|
||||
let rawheaderlines = zipWith toHeaderLine colwidths aligns
|
||||
let headerlines = starter <> T.intercalate separator rawheaderlines <>
|
||||
ender
|
||||
let padContent (align, w) t' =
|
||||
let padding = w - T.length t'
|
||||
halfpadding = padding `div` 2
|
||||
in case align of
|
||||
AlignRight -> T.replicate padding " " <> t'
|
||||
AlignCenter -> T.replicate halfpadding " " <> t' <>
|
||||
T.replicate (padding - halfpadding) " "
|
||||
_ -> t' <> T.replicate padding " "
|
||||
let toRow xs = starter <> T.intercalate separator
|
||||
(zipWith padContent (zip aligns colwidths) xs) <>
|
||||
ender
|
||||
let table' = toRow rawheaders <> "\n" <> headerlines <> "\n" <>
|
||||
T.intercalate "\n" (map toRow rawrows)
|
||||
return (node (CUSTOM_BLOCK table' mempty) [] :
|
||||
if null capt
|
||||
then ns
|
||||
else capt' : ns)
|
||||
else do -- fall back to raw HTML
|
||||
s <- writeHtml5String def $! Pandoc nullMeta [t]
|
||||
return (node (HTML_BLOCK s) [] : ns)
|
||||
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)
|
||||
then do
|
||||
-- We construct a table manually as a CUSTOM_BLOCK, for
|
||||
-- two reasons: (1) cmark-gfm currently doesn't support
|
||||
-- rendering TABLE nodes; (2) we can align the column sides;
|
||||
-- (3) we can render the caption as a regular paragraph.
|
||||
let capt' = node PARAGRAPH (inlinesToNodes opts capt)
|
||||
-- backslash | in code and raw:
|
||||
let fixPipe (Code attr xs) =
|
||||
Code attr (T.replace "|" "\\|" xs)
|
||||
fixPipe (RawInline format xs) =
|
||||
RawInline format (T.replace "|" "\\|" xs)
|
||||
fixPipe x = x
|
||||
let toCell [Plain ils] = T.strip
|
||||
$ nodeToCommonmark [] Nothing
|
||||
$ node (CUSTOM_INLINE mempty mempty)
|
||||
$ inlinesToNodes opts
|
||||
$ walk (fixPipe . softBreakToSpace) ils
|
||||
toCell [Para ils] = T.strip
|
||||
$ nodeToCommonmark [] Nothing
|
||||
$ node (CUSTOM_INLINE mempty mempty)
|
||||
$ inlinesToNodes opts
|
||||
$ walk (fixPipe . softBreakToSpace) ils
|
||||
toCell [] = ""
|
||||
toCell xs = error $ "toCell encountered " ++ show xs
|
||||
let separator = " | "
|
||||
let starter = "| "
|
||||
let ender = " |"
|
||||
let rawheaders = map toCell headers
|
||||
let rawrows = map (map toCell) rows
|
||||
let maximum' [] = 0
|
||||
maximum' xs = maximum xs
|
||||
let colwidths = map (maximum' . map T.length) $
|
||||
transpose (rawheaders:rawrows)
|
||||
let toHeaderLine len AlignDefault = T.replicate len "-"
|
||||
toHeaderLine len AlignLeft = ":" <>
|
||||
T.replicate (max (len - 1) 1) "-"
|
||||
toHeaderLine len AlignRight =
|
||||
T.replicate (max (len - 1) 1) "-" <> ":"
|
||||
toHeaderLine len AlignCenter = ":" <>
|
||||
T.replicate (max (len - 2) 1) (T.pack "-") <> ":"
|
||||
let rawheaderlines = zipWith toHeaderLine colwidths aligns
|
||||
let headerlines = starter <> T.intercalate separator rawheaderlines <>
|
||||
ender
|
||||
let padContent (align, w) t' =
|
||||
let padding = w - T.length t'
|
||||
halfpadding = padding `div` 2
|
||||
in case align of
|
||||
AlignRight -> T.replicate padding " " <> t'
|
||||
AlignCenter -> T.replicate halfpadding " " <> t' <>
|
||||
T.replicate (padding - halfpadding) " "
|
||||
_ -> t' <> T.replicate padding " "
|
||||
let toRow xs = starter <> T.intercalate separator
|
||||
(zipWith padContent (zip aligns colwidths) xs) <>
|
||||
ender
|
||||
let table' = toRow rawheaders <> "\n" <> headerlines <> "\n" <>
|
||||
T.intercalate "\n" (map toRow rawrows)
|
||||
return (node (CUSTOM_BLOCK table' mempty) [] :
|
||||
if null capt
|
||||
then ns
|
||||
else capt' : ns)
|
||||
else do -- fall back to raw HTML
|
||||
s <- writeHtml5String def $! Pandoc nullMeta [t]
|
||||
return (node (HTML_BLOCK s) [] : ns)
|
||||
blockToNodes _ Null ns = return ns
|
||||
|
||||
inlinesToNodes :: WriterOptions -> [Inline] -> [Node]
|
||||
|
|
|
@ -255,7 +255,8 @@ blockToConTeXt (DefinitionList lst) =
|
|||
blockToConTeXt HorizontalRule = return $ "\\thinrule" <> blankline
|
||||
-- If this is ever executed, provide a default for the reference identifier.
|
||||
blockToConTeXt (Header level attr lst) = sectionHeader attr level lst
|
||||
blockToConTeXt (Table caption aligns widths heads rows) = do
|
||||
blockToConTeXt (Table _ blkCapt specs _ thead tbody tfoot) = do
|
||||
let (caption, aligns, widths, heads, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
opts <- gets stOptions
|
||||
let tabl = if isEnabled Ext_ntb opts
|
||||
then Ntb
|
||||
|
|
|
@ -29,6 +29,7 @@ import Text.Pandoc.Lua (Global (..), LuaException (LuaException),
|
|||
runLua, setGlobals)
|
||||
import Text.Pandoc.Lua.Util (addField, dofileWithTraceback)
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Shared (toLegacyTable)
|
||||
import Text.Pandoc.Templates (renderTemplate)
|
||||
import qualified Text.Pandoc.UTF8 as UTF8
|
||||
import Text.Pandoc.Writers.Shared
|
||||
|
@ -149,8 +150,9 @@ blockToCustom (CodeBlock attr str) =
|
|||
blockToCustom (BlockQuote blocks) =
|
||||
Lua.callFunc "BlockQuote" (Stringify blocks)
|
||||
|
||||
blockToCustom (Table capt aligns widths headers rows) =
|
||||
let aligns' = map show aligns
|
||||
blockToCustom (Table _ blkCapt specs _ thead tbody tfoot) =
|
||||
let (capt, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
aligns' = map show aligns
|
||||
capt' = Stringify capt
|
||||
headers' = map Stringify headers
|
||||
rows' = map (map Stringify) rows
|
||||
|
|
|
@ -263,7 +263,8 @@ blockToDocbook _ b@(RawBlock f str)
|
|||
report $ BlockNotRendered b
|
||||
return empty
|
||||
blockToDocbook _ HorizontalRule = return empty -- not semantic
|
||||
blockToDocbook opts (Table caption aligns widths headers rows) = do
|
||||
blockToDocbook opts (Table _ blkCapt specs _ thead tbody tfoot) = do
|
||||
let (caption, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
captionDoc <- if null caption
|
||||
then return empty
|
||||
else inTagsIndented "title" <$>
|
||||
|
|
|
@ -970,7 +970,8 @@ blockToOpenXML' _ HorizontalRule = do
|
|||
$ mknode "v:rect" [("style","width:0;height:1.5pt"),
|
||||
("o:hralign","center"),
|
||||
("o:hrstd","t"),("o:hr","t")] () ]
|
||||
blockToOpenXML' opts (Table caption aligns widths headers rows) = do
|
||||
blockToOpenXML' opts (Table _ blkCapt specs _ thead tbody tfoot) = do
|
||||
let (caption, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
setFirstPara
|
||||
modify $ \s -> s { stInTable = True }
|
||||
let captionStr = stringify caption
|
||||
|
@ -993,11 +994,11 @@ blockToOpenXML' opts (Table caption aligns widths headers rows) = do
|
|||
$ mknode "w:bottom" [("w:val","single")] ()
|
||||
, mknode "w:vAlign" [("w:val","bottom")] () ]
|
||||
compactStyle <- pStyleM "Compact"
|
||||
let emptyCell = [mknode "w:p" [] [mknode "w:pPr" [] [compactStyle]]]
|
||||
let emptyCell' = [mknode "w:p" [] [mknode "w:pPr" [] [compactStyle]]]
|
||||
let mkcell border contents = mknode "w:tc" []
|
||||
$ [ borderProps | border ] ++
|
||||
if null contents
|
||||
then emptyCell
|
||||
then emptyCell'
|
||||
else contents
|
||||
let mkrow border cells = mknode "w:tr" [] $
|
||||
[mknode "w:trPr" [] [
|
||||
|
|
|
@ -35,7 +35,7 @@ import Text.Pandoc.ImageSize
|
|||
import Text.Pandoc.Logging
|
||||
import Text.Pandoc.Options (WrapOption (..), WriterOptions (writerTableOfContents, writerTemplate, writerWrapText))
|
||||
import Text.Pandoc.Shared (camelCaseToHyphenated, escapeURI, isURI, linesToPara,
|
||||
removeFormatting, trimr, tshow)
|
||||
removeFormatting, trimr, tshow, toLegacyTable)
|
||||
import Text.Pandoc.Templates (renderTemplate)
|
||||
import Text.DocLayout (render, literal)
|
||||
import Text.Pandoc.Writers.Shared (defField, metaToContext)
|
||||
|
@ -166,7 +166,8 @@ blockToDokuWiki opts (BlockQuote blocks) = do
|
|||
then return $ T.unlines $ map ("> " <>) $ T.lines contents
|
||||
else return $ "<HTML><blockquote>\n" <> contents <> "</blockquote></HTML>"
|
||||
|
||||
blockToDokuWiki opts (Table capt aligns _ headers rows) = do
|
||||
blockToDokuWiki opts (Table _ blkCapt specs _ thead tbody tfoot) = do
|
||||
let (capt, aligns, _, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
captionDoc <- if null capt
|
||||
then return ""
|
||||
else do
|
||||
|
|
|
@ -40,7 +40,7 @@ import Text.Pandoc.Definition
|
|||
import Text.Pandoc.Logging
|
||||
import Text.Pandoc.Options (HTMLMathMethod (..), WriterOptions (..), def)
|
||||
import Text.Pandoc.Shared (capitalize, isURI, orderedListMarkers,
|
||||
makeSections, tshow)
|
||||
makeSections, tshow, toLegacyTable)
|
||||
import Text.Pandoc.Writers.Shared (lookupMetaString)
|
||||
|
||||
-- | Data to be written at the end of the document:
|
||||
|
@ -334,17 +334,18 @@ blockToXml h@Header{} = do
|
|||
report $ BlockNotRendered h
|
||||
return []
|
||||
blockToXml HorizontalRule = return [ el "empty-line" () ]
|
||||
blockToXml (Table caption aligns _ headers rows) = do
|
||||
blockToXml (Table _ blkCapt specs _ thead tbody tfoot) = do
|
||||
let (caption, aligns, _, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
hd <- 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]
|
||||
where
|
||||
mkrow :: PandocMonad m => String -> [TableCell] -> [Alignment] -> FBM m Content
|
||||
mkrow :: PandocMonad m => String -> [[Block]] -> [Alignment] -> FBM m Content
|
||||
mkrow tag cells aligns' =
|
||||
el "tr" <$> mapM (mkcell tag) (zip cells aligns')
|
||||
--
|
||||
mkcell :: PandocMonad m => String -> (TableCell, Alignment) -> FBM m Content
|
||||
mkcell :: PandocMonad m => String -> ([Block], Alignment) -> FBM m Content
|
||||
mkcell tag (cell, align) = do
|
||||
cblocks <- cMapM blockToXml cell
|
||||
return $ el tag ([align_attr align], cblocks)
|
||||
|
|
|
@ -885,7 +885,8 @@ blockToHtml opts (DefinitionList lst) = do
|
|||
return $ mconcat $ nl opts : term' : nl opts :
|
||||
intersperse (nl opts) defs') lst
|
||||
defList opts contents
|
||||
blockToHtml opts (Table capt aligns widths headers rows') = do
|
||||
blockToHtml opts (Table _ blkCapt specs _ thead tbody tfoot) = do
|
||||
let (capt, aligns, widths, headers, rows') = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
captionDoc <- if null capt
|
||||
then return mempty
|
||||
else do
|
||||
|
|
|
@ -115,7 +115,8 @@ blockToHaddock _ (CodeBlock (_,_,_) str) =
|
|||
-- Nothing in haddock corresponds to block quotes:
|
||||
blockToHaddock opts (BlockQuote blocks) =
|
||||
blockListToHaddock opts blocks
|
||||
blockToHaddock opts (Table caption aligns widths headers rows) = do
|
||||
blockToHaddock opts (Table _ blkCapt specs _ thead tbody tfoot) = do
|
||||
let (caption, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
caption' <- inlineListToHaddock opts caption
|
||||
let caption'' = if null caption
|
||||
then empty
|
||||
|
|
|
@ -321,8 +321,9 @@ blockToICML opts style (Header lvl (_, cls, _) lst) =
|
|||
else ""
|
||||
in parStyle opts stl lst
|
||||
blockToICML _ _ HorizontalRule = return empty -- we could insert a page break instead
|
||||
blockToICML opts style (Table caption aligns widths headers rows) =
|
||||
let style' = tableName : style
|
||||
blockToICML opts style (Table _ blkCapt specs _ thead tbody tfoot) =
|
||||
let (caption, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
style' = tableName : style
|
||||
noHeader = all null headers
|
||||
nrHeaders = if noHeader
|
||||
then "0"
|
||||
|
|
|
@ -97,7 +97,7 @@ addAttachment (Image attr lab (src,tit))
|
|||
return $ Image attr lab ("attachment:" <> src, tit)
|
||||
addAttachment x = return x
|
||||
|
||||
extractCells :: PandocMonad m => WriterOptions -> [Block] -> m [Cell a]
|
||||
extractCells :: PandocMonad m => WriterOptions -> [Block] -> m [Ipynb.Cell a]
|
||||
extractCells _ [] = return []
|
||||
extractCells opts (Div (_id,classes,kvs) xs : bs)
|
||||
| "cell" `elem` classes
|
||||
|
@ -106,7 +106,7 @@ extractCells opts (Div (_id,classes,kvs) xs : bs)
|
|||
(newdoc, attachments) <-
|
||||
runStateT (walkM addAttachment (Pandoc nullMeta xs)) mempty
|
||||
source <- writeMarkdown opts{ writerTemplate = Nothing } newdoc
|
||||
(Cell{
|
||||
(Ipynb.Cell{
|
||||
cellType = Markdown
|
||||
, cellSource = Source $ breakLines $ T.stripEnd source
|
||||
, cellMetadata = meta
|
||||
|
@ -123,7 +123,7 @@ extractCells opts (Div (_id,classes,kvs) xs : bs)
|
|||
let meta = pairsToJSONMeta kvs
|
||||
outputs <- catMaybes <$> mapM blockToOutput rest
|
||||
let exeCount = lookup "execution_count" kvs >>= safeRead
|
||||
(Cell{
|
||||
(Ipynb.Cell{
|
||||
cellType = Ipynb.Code {
|
||||
codeExecutionCount = exeCount
|
||||
, codeOutputs = outputs
|
||||
|
@ -143,7 +143,7 @@ extractCells opts (Div (_id,classes,kvs) xs : bs)
|
|||
"markdown" -> "text/markdown"
|
||||
"rst" -> "text/x-rst"
|
||||
_ -> f
|
||||
(Cell{
|
||||
(Ipynb.Cell{
|
||||
cellType = Raw
|
||||
, cellSource = Source $ breakLines raw
|
||||
, cellMetadata = if format' == "ipynb" -- means no format given
|
||||
|
@ -156,7 +156,7 @@ extractCells opts (CodeBlock (_id,classes,kvs) raw : bs)
|
|||
| "code" `elem` classes = do
|
||||
let meta = pairsToJSONMeta kvs
|
||||
let exeCount = lookup "execution_count" kvs >>= safeRead
|
||||
(Cell{
|
||||
(Ipynb.Cell{
|
||||
cellType = Ipynb.Code {
|
||||
codeExecutionCount = exeCount
|
||||
, codeOutputs = []
|
||||
|
|
|
@ -356,21 +356,25 @@ blockToJATS _ b@(RawBlock f str)
|
|||
report $ BlockNotRendered b
|
||||
return empty
|
||||
blockToJATS _ HorizontalRule = return empty -- not semantic
|
||||
blockToJATS opts (Table [] aligns widths headers rows) = do
|
||||
let percent w = tshow (truncate (100*w) :: Integer) <> "*"
|
||||
let coltags = vcat $ zipWith (\w al -> selfClosingTag "col"
|
||||
([("width", percent w) | w > 0] ++
|
||||
[("align", alignmentToText al)])) widths aligns
|
||||
thead <- if all null headers
|
||||
then return empty
|
||||
else inTagsIndented "thead" <$> tableRowToJATS opts True headers
|
||||
tbody <- (inTagsIndented "tbody" . vcat) <$>
|
||||
mapM (tableRowToJATS opts False) rows
|
||||
return $ inTags True "table" [] $ coltags $$ thead $$ tbody
|
||||
blockToJATS opts (Table caption aligns widths headers rows) = do
|
||||
captionDoc <- inTagsIndented "caption" <$> blockToJATS opts (Para caption)
|
||||
tbl <- blockToJATS opts (Table [] aligns widths headers rows)
|
||||
return $ inTags True "table-wrap" [] $ captionDoc $$ tbl
|
||||
blockToJATS opts (Table _ blkCapt specs _ th tb tf) =
|
||||
case toLegacyTable blkCapt specs th tb tf of
|
||||
([], aligns, widths, headers, rows) -> captionlessTable aligns widths headers rows
|
||||
(caption, aligns, widths, headers, rows) -> do
|
||||
captionDoc <- inTagsIndented "caption" <$> blockToJATS opts (Para caption)
|
||||
tbl <- captionlessTable aligns widths headers rows
|
||||
return $ inTags True "table-wrap" [] $ captionDoc $$ tbl
|
||||
where
|
||||
captionlessTable aligns widths headers rows = do
|
||||
let percent w = tshow (truncate (100*w) :: Integer) <> "*"
|
||||
let coltags = vcat $ zipWith (\w al -> selfClosingTag "col"
|
||||
([("width", percent w) | w > 0] ++
|
||||
[("align", alignmentToText al)])) widths aligns
|
||||
thead <- if all null headers
|
||||
then return empty
|
||||
else inTagsIndented "thead" <$> tableRowToJATS opts True headers
|
||||
tbody <- (inTagsIndented "tbody" . vcat) <$>
|
||||
mapM (tableRowToJATS opts False) rows
|
||||
return $ inTags True "table" [] $ coltags $$ thead $$ tbody
|
||||
|
||||
alignmentToText :: Alignment -> Text
|
||||
alignmentToText alignment = case alignment of
|
||||
|
|
|
@ -26,7 +26,7 @@ import Text.Pandoc.Class.PandocMonad (PandocMonad)
|
|||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Options (WriterOptions (writerTemplate, writerWrapText),
|
||||
WrapOption (..))
|
||||
import Text.Pandoc.Shared (linesToPara, stringify)
|
||||
import Text.Pandoc.Shared (linesToPara, stringify, toLegacyTable)
|
||||
import Text.Pandoc.Templates (renderTemplate)
|
||||
import Text.Pandoc.Writers.Math (texMathToInlines)
|
||||
import Text.Pandoc.Writers.Shared (defField, metaToContext)
|
||||
|
@ -98,7 +98,8 @@ toJiraBlocks blocks = do
|
|||
Plain xs -> singleton . Jira.Para <$> toJiraInlines xs
|
||||
RawBlock fmt cs -> rawBlockToJira fmt cs
|
||||
Null -> return mempty
|
||||
Table _ _ _ hd body -> singleton <$> do
|
||||
Table _ blkCapt specs _ thead tbody tfoot -> singleton <$> do
|
||||
let (_, _, _, hd, body) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
headerRow <- if all null hd
|
||||
then pure Nothing
|
||||
else Just <$> toRow Jira.HeaderCell hd
|
||||
|
@ -112,7 +113,7 @@ toJiraBlocks blocks = do
|
|||
|
||||
toRow :: PandocMonad m
|
||||
=> ([Jira.Block] -> Jira.Cell)
|
||||
-> [TableCell]
|
||||
-> [[Block]]
|
||||
-> JiraConverter m Jira.Row
|
||||
toRow mkCell cells = Jira.Row <$>
|
||||
mapM (fmap mkCell . toJiraBlocks) cells
|
||||
|
|
|
@ -759,7 +759,8 @@ blockToLaTeX (Header level (id',classes,_) lst) = do
|
|||
hdr <- sectionHeader classes id' level lst
|
||||
modify $ \s -> s{stInHeading = False}
|
||||
return hdr
|
||||
blockToLaTeX (Table caption aligns widths heads rows) = do
|
||||
blockToLaTeX (Table _ blkCapt specs _ thead tbody tfoot) = do
|
||||
let (caption, aligns, widths, heads, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
(captionText, captForLof, captNotes) <- getCaption False caption
|
||||
let toHeaders hs = do contents <- tableRowToLaTeX True aligns widths hs
|
||||
return ("\\toprule" $$ contents $$ "\\midrule")
|
||||
|
|
|
@ -139,8 +139,9 @@ blockToMan opts (CodeBlock _ str) = return $
|
|||
blockToMan opts (BlockQuote blocks) = do
|
||||
contents <- blockListToMan opts blocks
|
||||
return $ literal ".RS" $$ contents $$ literal ".RE"
|
||||
blockToMan opts (Table caption alignments widths headers rows) =
|
||||
let aligncode AlignLeft = "l"
|
||||
blockToMan opts (Table _ blkCapt specs _ thead tbody tfoot) =
|
||||
let (caption, alignments, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
aligncode AlignLeft = "l"
|
||||
aligncode AlignRight = "r"
|
||||
aligncode AlignCenter = "c"
|
||||
aligncode AlignDefault = "l"
|
||||
|
|
|
@ -574,14 +574,15 @@ blockToMarkdown' opts (BlockQuote blocks) = do
|
|||
else if plain then " " else "> "
|
||||
contents <- blockListToMarkdown opts blocks
|
||||
return $ (prefixed leader contents) <> blankline
|
||||
blockToMarkdown' opts t@(Table caption aligns widths headers rows) = do
|
||||
blockToMarkdown' opts t@(Table _ blkCapt specs _ thead tbody tfoot) = do
|
||||
let (caption, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
let numcols = maximum (length aligns : length widths :
|
||||
map length (headers:rows))
|
||||
caption' <- inlineListToMarkdown opts caption
|
||||
let caption'' = if null caption || not (isEnabled Ext_table_captions opts)
|
||||
then blankline
|
||||
else blankline $$ (": " <> caption') $$ blankline
|
||||
let hasSimpleCells = onlySimpleTableCells $ headers:rows
|
||||
let hasSimpleCells = onlySimpleTableCells $ thead <> tbody <> tfoot
|
||||
let isSimple = hasSimpleCells && all (==0) widths
|
||||
let isPlainBlock (Plain _) = True
|
||||
isPlainBlock _ = False
|
||||
|
|
|
@ -150,7 +150,8 @@ blockToMediaWiki (BlockQuote blocks) = do
|
|||
contents <- blockListToMediaWiki blocks
|
||||
return $ "<blockquote>" <> contents <> "</blockquote>"
|
||||
|
||||
blockToMediaWiki (Table capt aligns widths headers rows') = do
|
||||
blockToMediaWiki (Table _ blkCapt specs _ thead tbody tfoot) = do
|
||||
let (capt, aligns, widths, headers, rows') = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
caption <- if null capt
|
||||
then return ""
|
||||
else do
|
||||
|
|
|
@ -215,8 +215,9 @@ blockToMs opts (BlockQuote blocks) = do
|
|||
contents <- blockListToMs opts blocks
|
||||
setFirstPara
|
||||
return $ literal ".QS" $$ contents $$ literal ".QE"
|
||||
blockToMs opts (Table caption alignments widths headers rows) =
|
||||
let aligncode AlignLeft = "l"
|
||||
blockToMs opts (Table _ blkCapt specs _ thead tbody tfoot) =
|
||||
let (caption, alignments, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
aligncode AlignLeft = "l"
|
||||
aligncode AlignRight = "r"
|
||||
aligncode AlignCenter = "c"
|
||||
aligncode AlignDefault = "l"
|
||||
|
|
|
@ -150,8 +150,8 @@ flatBlockListToMuse [] = return mempty
|
|||
|
||||
simpleTable :: PandocMonad m
|
||||
=> [Inline]
|
||||
-> [TableCell]
|
||||
-> [[TableCell]]
|
||||
-> [[Block]]
|
||||
-> [[[Block]]]
|
||||
-> Muse m (Doc Text)
|
||||
simpleTable caption headers rows = do
|
||||
topLevel <- asks envTopLevel
|
||||
|
@ -259,17 +259,18 @@ blockToMuse (Header level (ident,_,_) inlines) = do
|
|||
return $ blankline <> attr' $$ nowrap (header' <> contents) <> blankline
|
||||
-- https://www.gnu.org/software/emacs-muse/manual/muse.html#Horizontal-Rules-and-Anchors
|
||||
blockToMuse HorizontalRule = return $ blankline $$ "----" $$ blankline
|
||||
blockToMuse (Table caption aligns widths headers rows) =
|
||||
blockToMuse (Table _ blkCapt specs _ thead tbody tfoot) =
|
||||
if isSimple && numcols > 1
|
||||
then simpleTable caption headers rows
|
||||
else do
|
||||
opts <- asks envOptions
|
||||
gridTable opts blocksToDoc True (map (const AlignDefault) aligns) widths headers rows
|
||||
where
|
||||
(caption, aligns, widths, headers, rows) = toLegacyTable 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 (headers:rows) && all (== 0) widths
|
||||
isSimple = onlySimpleTableCells (thead <> tbody <> tfoot) && all (== 0) widths
|
||||
blockToMuse (Div _ bs) = flatBlockListToMuse bs
|
||||
blockToMuse Null = return empty
|
||||
|
||||
|
|
|
@ -40,12 +40,33 @@ prettyBlock (DefinitionList items) = "DefinitionList" $$
|
|||
prettyList (map deflistitem items)
|
||||
where deflistitem (term, defs) = "(" <> text (show term) <> "," <> cr <>
|
||||
nest 1 (prettyList $ map (prettyList . map prettyBlock) defs) <> ")"
|
||||
prettyBlock (Table caption aligns widths header rows) =
|
||||
"Table " <> text (show caption) <> " " <> text (show aligns) <> " " <>
|
||||
text (show widths) $$
|
||||
prettyRow header $$
|
||||
prettyList (map prettyRow rows)
|
||||
where prettyRow cols = prettyList (map (prettyList . map prettyBlock) cols)
|
||||
prettyBlock (Table attr blkCapt specs rhs thead tbody tfoot) =
|
||||
mconcat [ "Table "
|
||||
, text (show attr)
|
||||
, " "
|
||||
, prettyCaption blkCapt
|
||||
, " "
|
||||
, text (show specs)
|
||||
, " "
|
||||
, text (show rhs) ] $$
|
||||
prettyRows thead $$
|
||||
prettyRows tbody $$
|
||||
prettyRows tfoot
|
||||
where prettyRows = prettyList . map prettyRow
|
||||
prettyRow (Row a body) =
|
||||
text ("Row " <> show a) $$ prettyList (map prettyCell body)
|
||||
prettyCell (Cell a ma h w b) =
|
||||
mconcat [ "Cell "
|
||||
, text (show a)
|
||||
, " "
|
||||
, text (showsPrec 11 ma "")
|
||||
, " "
|
||||
, text (show h)
|
||||
, " "
|
||||
, text (show w) ] $$
|
||||
prettyList (map prettyBlock b)
|
||||
prettyCaption (Caption mshort body) =
|
||||
"(Caption " <> text (showsPrec 11 mshort "") $$ prettyList (map prettyBlock body) <> ")"
|
||||
prettyBlock (Div attr blocks) =
|
||||
text ("Div " <> show attr) $$ prettyList (map prettyBlock blocks)
|
||||
prettyBlock block = text $ show block
|
||||
|
|
|
@ -31,7 +31,7 @@ import Text.Pandoc.Definition
|
|||
import Text.Pandoc.Logging
|
||||
import Text.Pandoc.Options
|
||||
import Text.DocLayout
|
||||
import Text.Pandoc.Shared (linesToPara, tshow)
|
||||
import Text.Pandoc.Shared (linesToPara, tshow, toLegacyTable)
|
||||
import Text.Pandoc.Templates (renderTemplate)
|
||||
import qualified Text.Pandoc.Translations as Term (Term(Figure, Table))
|
||||
import Text.Pandoc.Writers.Math
|
||||
|
@ -359,7 +359,9 @@ blockToOpenDocument o bs
|
|||
| BulletList b <- bs = setFirstPara >> bulletListToOpenDocument o b
|
||||
| OrderedList a b <- bs = setFirstPara >> orderedList a b
|
||||
| CodeBlock _ s <- bs = setFirstPara >> preformatted s
|
||||
| Table c a w h r <- bs = setFirstPara >> table c a w h r
|
||||
| Table _ bc s _ th tb tf
|
||||
<- bs = let (c, a, w, h, r) = toLegacyTable bc s th tb tf
|
||||
in setFirstPara >> table c a w h r
|
||||
| HorizontalRule <- bs = setFirstPara >> return (selfClosingTag "text:p"
|
||||
[ ("text:style-name", "Horizontal_20_Line") ])
|
||||
| RawBlock f s <- bs = if f == Format "opendocument"
|
||||
|
|
|
@ -183,7 +183,8 @@ blockToOrg (BlockQuote blocks) = do
|
|||
contents <- blockListToOrg blocks
|
||||
return $ blankline $$ "#+BEGIN_QUOTE" $$
|
||||
nest 2 contents $$ "#+END_QUOTE" $$ blankline
|
||||
blockToOrg (Table caption' _ _ headers rows) = do
|
||||
blockToOrg (Table _ blkCapt specs _ thead tbody tfoot) = do
|
||||
let (caption', _, _, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
caption'' <- inlineListToOrg caption'
|
||||
let caption = if null caption'
|
||||
then empty
|
||||
|
|
|
@ -977,10 +977,10 @@ graphicToElement tableWidth (Tbl tblPr hdrCells rows) = do
|
|||
headers' <- mapM cellToOpenXML hdrCells
|
||||
rows' <- mapM (mapM cellToOpenXML) rows
|
||||
let borderProps = mknode "a:tcPr" [] ()
|
||||
let emptyCell = [mknode "a:p" [] [mknode "a:pPr" [] ()]]
|
||||
let emptyCell' = [mknode "a:p" [] [mknode "a:pPr" [] ()]]
|
||||
let mkcell border contents = mknode "a:tc" []
|
||||
$ (if null contents
|
||||
then emptyCell
|
||||
then emptyCell'
|
||||
else contents) <> [ borderProps | border ]
|
||||
let mkrow border cells = mknode "a:tr" [("h", "0")] $ map (mkcell border) cells
|
||||
|
||||
|
|
|
@ -54,7 +54,7 @@ import Text.Pandoc.Logging
|
|||
import Text.Pandoc.Walk
|
||||
import Data.Time (UTCTime)
|
||||
import qualified Text.Pandoc.Shared as Shared -- so we don't overlap "Element"
|
||||
import Text.Pandoc.Shared (tshow)
|
||||
import Text.Pandoc.Shared (tshow, toLegacyTable)
|
||||
import Text.Pandoc.Writers.Shared (lookupMetaInlines, lookupMetaBlocks
|
||||
, lookupMetaString, toTableOfContents)
|
||||
import qualified Data.Map as M
|
||||
|
@ -201,13 +201,17 @@ data Shape = Pic PicProps FilePath [ParaElem]
|
|||
| RawOOXMLShape T.Text
|
||||
deriving (Show, Eq)
|
||||
|
||||
type Cell = [Paragraph]
|
||||
type TableCell = [Paragraph]
|
||||
|
||||
-- TODO: remove when better handling of new
|
||||
-- tables is implemented
|
||||
type SimpleCell = [Block]
|
||||
|
||||
data TableProps = TableProps { tblPrFirstRow :: Bool
|
||||
, tblPrBandRow :: Bool
|
||||
} deriving (Show, Eq)
|
||||
|
||||
data Graphic = Tbl TableProps [Cell] [[Cell]]
|
||||
data Graphic = Tbl TableProps [TableCell] [[TableCell]]
|
||||
deriving (Show, Eq)
|
||||
|
||||
|
||||
|
@ -503,7 +507,7 @@ multiParBullet (b:bs) = do
|
|||
concatMapM blockToParagraphs bs
|
||||
return $ p ++ ps
|
||||
|
||||
cellToParagraphs :: Alignment -> TableCell -> Pres [Paragraph]
|
||||
cellToParagraphs :: Alignment -> SimpleCell -> Pres [Paragraph]
|
||||
cellToParagraphs algn tblCell = do
|
||||
paras <- mapM blockToParagraphs tblCell
|
||||
let alignment = case algn of
|
||||
|
@ -514,7 +518,7 @@ cellToParagraphs algn tblCell = do
|
|||
paras' = map (map (\p -> p{paraProps = (paraProps p){pPropAlign = alignment}})) paras
|
||||
return $ concat paras'
|
||||
|
||||
rowToParagraphs :: [Alignment] -> [TableCell] -> Pres [[Paragraph]]
|
||||
rowToParagraphs :: [Alignment] -> [SimpleCell] -> Pres [[Paragraph]]
|
||||
rowToParagraphs algns tblCells = do
|
||||
-- We have to make sure we have the right number of alignments
|
||||
let pairs = zip (algns ++ repeat AlignDefault) tblCells
|
||||
|
@ -537,7 +541,8 @@ blockToShape (Para (il:_)) | Link _ (il':_) target <- il
|
|||
, Image attr ils (url, _) <- il' =
|
||||
(withAttr attr . Pic def{picPropLink = Just $ ExternalTarget target} (T.unpack url))
|
||||
<$> inlinesToParElems ils
|
||||
blockToShape (Table caption algn _ hdrCells rows) = do
|
||||
blockToShape (Table _ blkCapt specs _ thead tbody tfoot) = do
|
||||
let (caption, algn, _, hdrCells, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
caption' <- inlinesToParElems caption
|
||||
hdrCells' <- rowToParagraphs algn hdrCells
|
||||
rows' <- mapM (rowToParagraphs algn) rows
|
||||
|
|
|
@ -284,7 +284,8 @@ blockToRST (CodeBlock (_,classes,kvs) str) = do
|
|||
blockToRST (BlockQuote blocks) = do
|
||||
contents <- blockListToRST blocks
|
||||
return $ nest 3 contents <> blankline
|
||||
blockToRST (Table caption aligns widths headers rows) = do
|
||||
blockToRST (Table _ blkCapt specs _ thead tbody tfoot) = do
|
||||
let (caption, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
caption' <- inlineListToRST caption
|
||||
let blocksToDoc opts bs = do
|
||||
oldOpts <- gets stOptions
|
||||
|
|
|
@ -254,7 +254,8 @@ blockToRTF indent alignment (Header level _ lst) = do
|
|||
contents <- inlinesToRTF lst
|
||||
return $ rtfPar indent 0 alignment $
|
||||
"\\b \\fs" <> tshow (40 - (level * 4)) <> " " <> contents
|
||||
blockToRTF indent alignment (Table caption aligns sizes headers rows) = do
|
||||
blockToRTF indent alignment (Table _ blkCapt specs _ thead tbody tfoot) = do
|
||||
let (caption, aligns, sizes, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
caption' <- inlinesToRTF caption
|
||||
header' <- if all null headers
|
||||
then return ""
|
||||
|
|
|
@ -194,7 +194,8 @@ blockToTEI _ HorizontalRule = return $
|
|||
-- | TEI Tables
|
||||
-- TEI Simple's tables are composed of cells and rows; other
|
||||
-- table info in the AST is here lossily discard.
|
||||
blockToTEI opts (Table _ _ _ headers rows) = do
|
||||
blockToTEI opts (Table _ blkCapt specs _ thead tbody tfoot) = do
|
||||
let (_, _, _, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
headers' <- tableHeadersToTEI opts headers
|
||||
rows' <- mapM (tableRowToTEI opts) rows
|
||||
return $ inTags True "table" [] $ headers' $$ vcat rows'
|
||||
|
|
|
@ -228,7 +228,8 @@ blockToTexinfo (Header level (ident,_,_) lst)
|
|||
seccmd 4 = return "@subsubsection "
|
||||
seccmd _ = throwError $ PandocSomeError "illegal seccmd level"
|
||||
|
||||
blockToTexinfo (Table caption aligns widths heads rows) = do
|
||||
blockToTexinfo (Table _ blkCapt specs _ thead tbody tfoot) = do
|
||||
let (caption, aligns, widths, heads, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
headers <- if all null heads
|
||||
then return empty
|
||||
else tableHeadToTexinfo aligns heads
|
||||
|
|
|
@ -168,44 +168,44 @@ blockToTextile opts (BlockQuote blocks) = do
|
|||
contents <- blockListToTextile opts blocks
|
||||
return $ "<blockquote>\n\n" <> contents <> "\n</blockquote>\n"
|
||||
|
||||
blockToTextile opts (Table [] aligns widths headers rows') |
|
||||
all (==0) widths = do
|
||||
hs <- mapM (liftM (("_. " <>) . stripTrailingNewlines) . blockListToTextile opts) headers
|
||||
let cellsToRow cells = "|" <> T.intercalate "|" cells <> "|"
|
||||
let header = if all null headers then "" else cellsToRow hs <> "\n"
|
||||
let blocksToCell (align, bs) = do
|
||||
contents <- stripTrailingNewlines <$> blockListToTextile opts bs
|
||||
let alignMarker = case align of
|
||||
AlignLeft -> "<. "
|
||||
AlignRight -> ">. "
|
||||
AlignCenter -> "=. "
|
||||
AlignDefault -> ""
|
||||
return $ alignMarker <> contents
|
||||
let rowToCells = mapM blocksToCell . zip aligns
|
||||
bs <- mapM rowToCells rows'
|
||||
let body = T.unlines $ map cellsToRow bs
|
||||
return $ header <> body
|
||||
|
||||
blockToTextile opts (Table capt aligns widths headers rows') = do
|
||||
let alignStrings = map alignmentToText aligns
|
||||
captionDoc <- if null capt
|
||||
then return ""
|
||||
else do
|
||||
c <- inlineListToTextile opts capt
|
||||
return $ "<caption>" <> c <> "</caption>\n"
|
||||
let percent w = tshow (truncate (100*w) :: Integer) <> "%"
|
||||
let coltags = if all (== 0.0) widths
|
||||
then ""
|
||||
else T.unlines $ map
|
||||
(\w -> "<col width=\"" <> percent w <> "\" />") widths
|
||||
head' <- if all null headers
|
||||
then return ""
|
||||
else do
|
||||
hs <- tableRowToTextile opts alignStrings 0 headers
|
||||
return $ "<thead>\n" <> hs <> "\n</thead>\n"
|
||||
body' <- zipWithM (tableRowToTextile opts alignStrings) [1..] rows'
|
||||
return $ "<table>\n" <> captionDoc <> coltags <> head' <>
|
||||
"<tbody>\n" <> T.unlines body' <> "</tbody>\n</table>\n"
|
||||
blockToTextile opts (Table _ blkCapt specs _ thead tbody tfoot)
|
||||
= case toLegacyTable blkCapt specs thead tbody tfoot of
|
||||
([], aligns, widths, headers, rows') | all (==0) widths -> do
|
||||
hs <- mapM (liftM (("_. " <>) . stripTrailingNewlines) . blockListToTextile opts) headers
|
||||
let cellsToRow cells = "|" <> T.intercalate "|" cells <> "|"
|
||||
let header = if all null headers then "" else cellsToRow hs <> "\n"
|
||||
let blocksToCell (align, bs) = do
|
||||
contents <- stripTrailingNewlines <$> blockListToTextile opts bs
|
||||
let alignMarker = case align of
|
||||
AlignLeft -> "<. "
|
||||
AlignRight -> ">. "
|
||||
AlignCenter -> "=. "
|
||||
AlignDefault -> ""
|
||||
return $ alignMarker <> contents
|
||||
let rowToCells = mapM blocksToCell . zip aligns
|
||||
bs <- mapM rowToCells rows'
|
||||
let body = T.unlines $ map cellsToRow bs
|
||||
return $ header <> body
|
||||
(capt, aligns, widths, headers, rows') -> do
|
||||
let alignStrings = map alignmentToText aligns
|
||||
captionDoc <- if null capt
|
||||
then return ""
|
||||
else do
|
||||
c <- inlineListToTextile opts capt
|
||||
return $ "<caption>" <> c <> "</caption>\n"
|
||||
let percent w = tshow (truncate (100*w) :: Integer) <> "%"
|
||||
let coltags = if all (== 0.0) widths
|
||||
then ""
|
||||
else T.unlines $ map
|
||||
(\w -> "<col width=\"" <> percent w <> "\" />") widths
|
||||
head' <- if all null headers
|
||||
then return ""
|
||||
else do
|
||||
hs <- tableRowToTextile opts alignStrings 0 headers
|
||||
return $ "<thead>\n" <> hs <> "\n</thead>\n"
|
||||
body' <- zipWithM (tableRowToTextile opts alignStrings) [1..] rows'
|
||||
return $ "<table>\n" <> captionDoc <> coltags <> head' <>
|
||||
"<tbody>\n" <> T.unlines body' <> "</tbody>\n</table>\n"
|
||||
|
||||
blockToTextile opts x@(BulletList items) = do
|
||||
oldUseTags <- gets stUseTags
|
||||
|
|
|
@ -122,7 +122,8 @@ blockToXWiki (DefinitionList items) = do
|
|||
return $ vcat contents <> if Text.null lev then "\n" else ""
|
||||
|
||||
-- TODO: support more features
|
||||
blockToXWiki (Table _ _ _ headers rows') = do
|
||||
blockToXWiki (Table _ blkCapt specs _ thead tbody tfoot) = do
|
||||
let (_, _, _, headers, rows') = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
headers' <- mapM (tableCellXWiki True) headers
|
||||
otherRows <- mapM formRow rows'
|
||||
return $ Text.unlines (Text.unwords headers':otherRows)
|
||||
|
|
|
@ -32,7 +32,7 @@ import Text.Pandoc.Logging
|
|||
import Text.Pandoc.Options (WrapOption (..),
|
||||
WriterOptions (writerTableOfContents, writerTemplate,
|
||||
writerWrapText))
|
||||
import Text.Pandoc.Shared (escapeURI, isURI, linesToPara, removeFormatting, trimr)
|
||||
import Text.Pandoc.Shared (escapeURI, isURI, linesToPara, removeFormatting, trimr, toLegacyTable)
|
||||
import Text.Pandoc.Templates (renderTemplate)
|
||||
import Text.Pandoc.Writers.Shared (defField, metaToContext)
|
||||
|
||||
|
@ -132,7 +132,8 @@ blockToZimWiki opts (BlockQuote blocks) = do
|
|||
contents <- blockListToZimWiki opts blocks
|
||||
return $ T.unlines $ map ("> " <>) $ T.lines contents
|
||||
|
||||
blockToZimWiki opts (Table capt aligns _ headers rows) = do
|
||||
blockToZimWiki opts (Table _ blkCapt specs _ thead tbody tfoot) = do
|
||||
let (capt, aligns, _, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
captionDoc <- if null capt
|
||||
then return ""
|
||||
else do
|
||||
|
|
|
@ -12,7 +12,10 @@ flags:
|
|||
packages:
|
||||
- '.'
|
||||
extra-deps:
|
||||
- pandoc-types-1.20
|
||||
# - pandoc-types-1.20
|
||||
# better-tables
|
||||
- git: git@github.com:despresc/pandoc-types
|
||||
commit: 5fef630269d29a818cde834c4cea50f129c7e2b8
|
||||
- texmath-0.12.0.1
|
||||
- haddock-library-1.8.0
|
||||
- skylighting-0.8.3.2
|
||||
|
|
|
@ -296,7 +296,7 @@ tests = [ testGroup "inlines"
|
|||
T.unlines [ "| foo | bar |"
|
||||
, "| bat | baz |"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
|
||||
table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
|
||||
[]
|
||||
[[plain "foo", plain "bar"]
|
||||
,[plain "bat", plain "baz"]]
|
||||
|
@ -304,7 +304,7 @@ tests = [ testGroup "inlines"
|
|||
T.unlines [ "^ foo ^ bar ^"
|
||||
, "| bat | baz |"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
|
||||
table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
|
||||
[plain "foo", plain "bar"]
|
||||
[[plain "bat", plain "baz"]]
|
||||
, "Table with colspan" =:
|
||||
|
@ -312,7 +312,7 @@ tests = [ testGroup "inlines"
|
|||
, "| 1,0 | 1,1 ||"
|
||||
, "| 2,0 | 2,1 | 2,2 |"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0), (AlignDefault, 0.0)]
|
||||
table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing), (AlignDefault, Nothing)]
|
||||
[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"]
|
||||
|
|
|
@ -36,7 +36,7 @@ infix 4 =:
|
|||
(=:) = test latex
|
||||
|
||||
simpleTable' :: [Alignment] -> [[Blocks]] -> Blocks
|
||||
simpleTable' aligns = table "" (zip aligns (repeat 0.0))
|
||||
simpleTable' aligns = table "" (zip aligns (repeat Nothing))
|
||||
(map (const mempty) aligns)
|
||||
|
||||
tokUntokRt :: String -> Bool
|
||||
|
|
|
@ -122,12 +122,12 @@ tests = [
|
|||
testGroup "Tables" [
|
||||
"t1" =:
|
||||
".TS\nallbox;\nl l l.\na\tb\tc\nd\te\tf\n.TE"
|
||||
=?> table mempty (replicate 3 (AlignLeft, 0.0)) [] [
|
||||
=?> table mempty (replicate 3 (AlignLeft, Nothing)) [] [
|
||||
map (plain . str ) ["a", "b", "c"],
|
||||
map (plain . str ) ["d", "e", "f"]
|
||||
],
|
||||
"longcell" =:
|
||||
".TS\n;\nr.\nT{\na\nb\nc d\nT}\nf\n.TE"
|
||||
=?> table mempty [(AlignRight, 0.0)] [] [[plain $ text "a b c d"], [plain $ str "f"]]
|
||||
=?> table mempty [(AlignRight, Nothing)] [] [[plain $ text "a b c d"], [plain $ str "f"]]
|
||||
]
|
||||
]
|
||||
|
|
|
@ -15,6 +15,7 @@ module Tests.Readers.Muse (tests) where
|
|||
|
||||
import Prelude
|
||||
import Data.List (intersperse)
|
||||
import Data.Maybe (isNothing)
|
||||
import Data.Monoid (Any (..))
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
|
@ -25,7 +26,7 @@ import Tests.Helpers
|
|||
import Text.Pandoc
|
||||
import Text.Pandoc.Arbitrary ()
|
||||
import Text.Pandoc.Builder
|
||||
import Text.Pandoc.Shared (underlineSpan)
|
||||
import Text.Pandoc.Shared (underlineSpan, toLegacyTable)
|
||||
import Text.Pandoc.Walk
|
||||
|
||||
amuse :: Text -> Pandoc
|
||||
|
@ -45,20 +46,41 @@ spcSep = mconcat . intersperse space
|
|||
-- Tables don't round-trip yet
|
||||
--
|
||||
makeRoundTrip :: Block -> Block
|
||||
makeRoundTrip t@(Table _caption aligns widths headers rows) =
|
||||
makeRoundTrip t@(Table tattr blkCapt specs rhs thead tbody tfoot) =
|
||||
if isSimple && numcols > 1
|
||||
then t
|
||||
else Para [Str "table was here"]
|
||||
where numcols = maximum (length aligns : length widths : map length (headers:rows))
|
||||
hasSimpleCells = all isSimpleCell (concat (headers:rows))
|
||||
where (_, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
|
||||
numcols = maximum (length aligns : length widths : map length (headers:rows))
|
||||
hasSimpleCells = all isSimpleRow (thead <> tbody <> tfoot)
|
||||
isLineBreak LineBreak = Any True
|
||||
isLineBreak _ = Any False
|
||||
hasLineBreak = getAny . query isLineBreak
|
||||
isSimple = hasSimpleCells && all (== 0) widths
|
||||
isSimpleCell [Plain ils] = not (hasLineBreak ils)
|
||||
isSimpleCell [Para ils ] = not (hasLineBreak ils)
|
||||
isSimpleCell [] = True
|
||||
isSimpleCell _ = False
|
||||
isSimple = and [ hasSimpleCells
|
||||
, all (== 0) widths
|
||||
, null tfoot
|
||||
, length thead == 1
|
||||
, isNullAttr tattr
|
||||
, rhs == 0
|
||||
, simpleCapt ]
|
||||
isNullAttr ("", [], []) = True
|
||||
isNullAttr _ = False
|
||||
isSimpleRow (Row attr body) = isNullAttr attr && all isSimpleCell body
|
||||
isSimpleCell (Cell attr ali h w body)
|
||||
= and [ h == 1
|
||||
, w == 1
|
||||
, isNullAttr attr
|
||||
, isNothing ali
|
||||
, isSimpleCellBody body ]
|
||||
isSimpleCellBody [Plain ils] = not (hasLineBreak ils)
|
||||
isSimpleCellBody [Para ils ] = not (hasLineBreak ils)
|
||||
isSimpleCellBody [] = True
|
||||
isSimpleCellBody _ = False
|
||||
simpleCapt = case blkCapt of
|
||||
Caption Nothing [Para _] -> True
|
||||
Caption Nothing [Plain _] -> True
|
||||
_ -> False
|
||||
|
||||
makeRoundTrip (OrderedList (start, LowerAlpha, _) items) = OrderedList (start, Decimal, Period) items
|
||||
makeRoundTrip (OrderedList (start, UpperAlpha, _) items) = OrderedList (start, Decimal, Period) items
|
||||
makeRoundTrip x = x
|
||||
|
@ -950,12 +972,12 @@ tests =
|
|||
, testGroup "Tables"
|
||||
[ "Two cell table" =:
|
||||
"One | Two" =?>
|
||||
table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
|
||||
table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
|
||||
[]
|
||||
[[plain "One", plain "Two"]]
|
||||
, "Table with multiple words" =:
|
||||
"One two | three four" =?>
|
||||
table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
|
||||
table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
|
||||
[]
|
||||
[[plain "One two", plain "three four"]]
|
||||
, "Not a table" =:
|
||||
|
@ -969,7 +991,7 @@ tests =
|
|||
[ "One | Two"
|
||||
, "Three | Four"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
|
||||
table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
|
||||
[]
|
||||
[[plain "One", plain "Two"],
|
||||
[plain "Three", plain "Four"]]
|
||||
|
@ -978,7 +1000,7 @@ tests =
|
|||
[ "First || Second"
|
||||
, "Third | Fourth"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
|
||||
table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
|
||||
[plain "First", plain "Second"]
|
||||
[[plain "Third", plain "Fourth"]]
|
||||
, "Table with two headers" =:
|
||||
|
@ -987,7 +1009,7 @@ tests =
|
|||
, "Second || header"
|
||||
, "Foo | bar"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
|
||||
table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
|
||||
[plain "First", plain "header"]
|
||||
[[plain "Second", plain "header"],
|
||||
[plain "Foo", plain "bar"]]
|
||||
|
@ -997,7 +1019,7 @@ tests =
|
|||
, "Baz || foo"
|
||||
, "Bar | baz"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
|
||||
table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
|
||||
[plain "Baz", plain "foo"]
|
||||
[[plain "Bar", plain "baz"],
|
||||
[plain "Foo", plain "bar"]]
|
||||
|
@ -1008,7 +1030,7 @@ tests =
|
|||
, "Second | row | there"
|
||||
, "|+ Table caption +|"
|
||||
] =?>
|
||||
table (text "Table caption") (replicate 3 (AlignDefault, 0.0))
|
||||
table (text "Table caption") (replicate 3 (AlignDefault, Nothing))
|
||||
[plain "Foo", plain "bar", plain "baz"]
|
||||
[[plain "First", plain "row", plain "here"],
|
||||
[plain "Second", plain "row", plain "there"]]
|
||||
|
@ -1017,7 +1039,7 @@ tests =
|
|||
[ "Foo | bar"
|
||||
, "|+ Table + caption +|"
|
||||
] =?>
|
||||
table (text "Table + caption") (replicate 2 (AlignDefault, 0.0))
|
||||
table (text "Table + caption") (replicate 2 (AlignDefault, Nothing))
|
||||
[]
|
||||
[[plain "Foo", plain "bar"]]
|
||||
, "Caption without table" =:
|
||||
|
@ -1029,7 +1051,7 @@ tests =
|
|||
, " Baz | foo"
|
||||
, " Bar | baz"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
|
||||
table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
|
||||
[]
|
||||
[[plain "Foo", plain "bar"],
|
||||
[plain "Baz", plain "foo"],
|
||||
|
@ -1041,7 +1063,7 @@ tests =
|
|||
, " bar |"
|
||||
, " || baz"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
|
||||
table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
|
||||
[plain "", plain "baz"]
|
||||
[[plain "", plain "Foo"],
|
||||
[plain "", plain ""],
|
||||
|
@ -1052,7 +1074,7 @@ tests =
|
|||
, " 4 | | 6"
|
||||
, " 7 | 8 | 9"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0), (AlignDefault, 0.0)]
|
||||
table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing), (AlignDefault, Nothing)]
|
||||
[]
|
||||
[[plain "1", plain "2", plain "3"],
|
||||
[plain "4", mempty, plain "6"],
|
||||
|
@ -1063,7 +1085,7 @@ tests =
|
|||
, "| foo | bar |"
|
||||
, "+-----+-----+"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
|
||||
table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
|
||||
[]
|
||||
[[para "foo", para "bar"]]
|
||||
, "Grid table inside list" =:
|
||||
|
@ -1072,7 +1094,7 @@ tests =
|
|||
, " | foo | bar |"
|
||||
, " +-----+-----+"
|
||||
] =?>
|
||||
bulletList [table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
|
||||
bulletList [table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
|
||||
[]
|
||||
[[para "foo", para "bar"]]]
|
||||
, "Grid table with two rows" =:
|
||||
|
@ -1083,7 +1105,7 @@ tests =
|
|||
, "| bat | baz |"
|
||||
, "+-----+-----+"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
|
||||
table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
|
||||
[]
|
||||
[[para "foo", para "bar"]
|
||||
,[para "bat", para "baz"]]
|
||||
|
@ -1095,9 +1117,9 @@ tests =
|
|||
, "|+---+|"
|
||||
, "+-----+"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, 0.0)]
|
||||
table mempty [(AlignDefault, Nothing)]
|
||||
[]
|
||||
[[table mempty [(AlignDefault, 0.0)]
|
||||
[[table mempty [(AlignDefault, Nothing)]
|
||||
[]
|
||||
[[para "foo"]]]]
|
||||
, "Grid table with example" =:
|
||||
|
@ -1108,7 +1130,7 @@ tests =
|
|||
, "| </example> |"
|
||||
, "+------------+"
|
||||
] =?>
|
||||
table mempty [(AlignDefault, 0.0)]
|
||||
table mempty [(AlignDefault, Nothing)]
|
||||
[]
|
||||
[[codeBlock "foo"]]
|
||||
]
|
||||
|
@ -1479,13 +1501,13 @@ tests =
|
|||
]
|
||||
, "Definition list with table" =:
|
||||
" foo :: bar | baz" =?>
|
||||
definitionList [ ("foo", [ table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
|
||||
definitionList [ ("foo", [ table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
|
||||
[]
|
||||
[[plain "bar", plain "baz"]]
|
||||
])]
|
||||
, "Definition list with table inside bullet list" =:
|
||||
" - foo :: bar | baz" =?>
|
||||
bulletList [definitionList [ ("foo", [ table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
|
||||
bulletList [definitionList [ ("foo", [ table mempty [(AlignDefault, Nothing), (AlignDefault, Nothing)]
|
||||
[]
|
||||
[[plain "bar", plain "baz"]]
|
||||
])]]
|
||||
|
|
|
@ -24,7 +24,7 @@ simpleTable' :: Int
|
|||
-> [Blocks]
|
||||
-> [[Blocks]]
|
||||
-> Blocks
|
||||
simpleTable' n = table "" (replicate n (AlignDefault, 0.0))
|
||||
simpleTable' n = table "" (replicate n (AlignDefault, Nothing))
|
||||
|
||||
tests :: [TestTree]
|
||||
tests =
|
||||
|
@ -121,7 +121,7 @@ tests =
|
|||
, "| 1 | One | foo |"
|
||||
, "| 2 | Two | bar |"
|
||||
] =?>
|
||||
table "" (zip [AlignCenter, AlignRight, AlignDefault] [0, 0, 0])
|
||||
table "" (zip [AlignCenter, AlignRight, AlignDefault] [Nothing, Nothing, Nothing])
|
||||
[]
|
||||
[ [ plain "Numbers", plain "Text", plain "More" ]
|
||||
, [ plain "1" , plain "One" , plain "foo" ]
|
||||
|
@ -143,7 +143,7 @@ tests =
|
|||
, "| 1 | One | foo |"
|
||||
, "| 2"
|
||||
] =?>
|
||||
table "" (zip [AlignCenter, AlignRight] [0, 0])
|
||||
table "" (zip [AlignCenter, AlignRight] [Nothing, Nothing])
|
||||
[ plain "Numbers", plain "Text" ]
|
||||
[ [ plain "1" , plain "One" , plain "foo" ]
|
||||
, [ plain "2" ]
|
||||
|
@ -155,7 +155,7 @@ tests =
|
|||
, "| 9 | 42 |"
|
||||
] =?>
|
||||
table "Hitchhiker's Multiplication Table"
|
||||
[(AlignDefault, 0), (AlignDefault, 0)]
|
||||
[(AlignDefault, Nothing), (AlignDefault, Nothing)]
|
||||
[]
|
||||
[ [ plain "x", plain "6" ]
|
||||
, [ plain "9", plain "42" ]
|
||||
|
|
|
@ -44,7 +44,7 @@ simpleTable' :: Int
|
|||
-> [Blocks]
|
||||
-> [[Blocks]]
|
||||
-> Blocks
|
||||
simpleTable' n = table "" (replicate n (AlignCenter, 0.0))
|
||||
simpleTable' n = table "" (replicate n (AlignCenter, Nothing))
|
||||
|
||||
tests :: [TestTree]
|
||||
tests =
|
||||
|
@ -398,7 +398,7 @@ tests =
|
|||
, "| 1 | One | foo |"
|
||||
, "| 2 | Two | bar |"
|
||||
] =?>
|
||||
table "" (zip [AlignCenter, AlignRight, AlignDefault] [0, 0, 0])
|
||||
table "" (zip [AlignCenter, AlignRight, AlignDefault] [Nothing, Nothing, Nothing])
|
||||
[]
|
||||
[ [ plain "Numbers", plain "Text", plain "More" ]
|
||||
, [ plain "1" , plain "One" , plain "foo" ]
|
||||
|
@ -415,7 +415,7 @@ tests =
|
|||
, "| 1 | One | foo |"
|
||||
, "| 2 "
|
||||
] =?>
|
||||
table "" (zip [AlignCenter, AlignLeft, AlignLeft] [0, 0, 0])
|
||||
table "" (zip [AlignCenter, AlignLeft, AlignLeft] [Nothing, Nothing, Nothing])
|
||||
[ plain "Numbers", plain "Text" , plain mempty ]
|
||||
[ [ plain "1" , plain "One" , plain "foo" ]
|
||||
, [ plain "2" , plain mempty , plain mempty ]
|
||||
|
|
|
@ -98,8 +98,8 @@ tests = [ testGroup "inline code"
|
|||
]
|
||||
, testGroup "natural tables"
|
||||
[ test contextNtb "table with header and caption" $
|
||||
let caption = text "Table 1"
|
||||
aligns = [(AlignRight, 0.0), (AlignLeft, 0.0), (AlignCenter, 0.0), (AlignDefault, 0.0)]
|
||||
let capt = text "Table 1"
|
||||
aligns = [(AlignRight, Nothing), (AlignLeft, Nothing), (AlignCenter, Nothing), (AlignDefault, Nothing)]
|
||||
headers = [plain $ text "Right",
|
||||
plain $ text "Left",
|
||||
plain $ text "Center",
|
||||
|
@ -116,7 +116,7 @@ tests = [ testGroup "inline code"
|
|||
plain $ text "3.2",
|
||||
plain $ text "3.3",
|
||||
plain $ text "3.4"]]
|
||||
in table caption aligns headers rows
|
||||
in table capt aligns headers rows
|
||||
=?> unlines [ "\\startplacetable[title={Table 1}]"
|
||||
, "\\startTABLE"
|
||||
, "\\startTABLEhead"
|
||||
|
|
|
@ -372,7 +372,7 @@ 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,0.0),(AlignDefault,0.0)]
|
||||
in table mempty [(AlignDefault,Nothing),(AlignDefault,Nothing)]
|
||||
[mempty, mempty] rows
|
||||
=?>
|
||||
unlines [ " Para 1.1 | Para 1.2"
|
||||
|
@ -389,11 +389,11 @@ tests = [ testGroup "block elements"
|
|||
, " Para 2.1 | Para 2.2"
|
||||
]
|
||||
, "table with header and caption" =:
|
||||
let caption = "Table 1"
|
||||
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 caption [(AlignDefault,0.0),(AlignDefault,0.0)]
|
||||
in table capt [(AlignDefault,Nothing),(AlignDefault,Nothing)]
|
||||
headers rows
|
||||
=?> unlines [ " header 1 || header 2"
|
||||
, " Para 1.1 | Para 1.2"
|
||||
|
|
|
@ -20,15 +20,27 @@
|
|||
</tbody>
|
||||
</table>
|
||||
^D
|
||||
[Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."] [AlignRight,AlignLeft,AlignCenter,AlignDefault] [0.0,0.0,0.0,0.0]
|
||||
[[Plain [Str "Right"]]
|
||||
,[Plain [Str "Left"]]
|
||||
,[Plain [Str "Center"]]
|
||||
,[Plain [Str "Default"]]]
|
||||
[[[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[Para [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."]]) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Right"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Left"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Center"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Default"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]]]
|
||||
[]]
|
||||
```
|
||||
|
||||
```
|
||||
|
@ -42,14 +54,26 @@
|
|||
</tr>
|
||||
</table>
|
||||
^D
|
||||
[Table [] [AlignRight,AlignLeft,AlignCenter,AlignRight] [0.0,0.0,0.0,0.0]
|
||||
[[]
|
||||
,[]
|
||||
,[]
|
||||
,[]]
|
||||
[[[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignRight,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]]]
|
||||
[]]
|
||||
```
|
||||
|
||||
|
|
|
@ -7,11 +7,22 @@
|
|||
line of text
|
||||
----- ------------------------------------------------
|
||||
^D
|
||||
[Table [] [AlignRight,AlignLeft] [8.333333333333333e-2,0.6805555555555556]
|
||||
[[]
|
||||
,[]]
|
||||
[[[Plain [Str "foo"]]
|
||||
,[Plain [Str "bar"]]]
|
||||
,[[Plain [Str "foo"]]
|
||||
,[Plain [Str "this",Space,Str "is",Space,Str "a",Space,Str "long",SoftBreak,Str "line",Space,Str "of",Space,Str "text"]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignRight,Just 8.333333333333333e-2),(AlignLeft,Just 0.6805555555555556)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "foo"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "bar"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "foo"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "this",Space,Str "is",Space,Str "a",Space,Str "long",SoftBreak,Str "line",Space,Str "of",Space,Str "text"]]]]
|
||||
[]]
|
||||
```
|
||||
|
|
|
@ -24,24 +24,46 @@ on Windows builds.
|
|||
| | |
|
||||
+---+---+
|
||||
^D
|
||||
[Table [] [AlignDefault,AlignDefault] [5.555555555555555e-2,5.555555555555555e-2]
|
||||
[[]
|
||||
,[]]
|
||||
[[[Plain [Str "1"]]
|
||||
,[Plain [Str "2"]]]
|
||||
,[[]
|
||||
,[]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Just 5.555555555555555e-2),(AlignDefault,Just 5.555555555555555e-2)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "2"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[]]
|
||||
```
|
||||
|
||||
```
|
||||
% pandoc -f native -t rst
|
||||
[Table [] [AlignDefault,AlignDefault] [5.555555555555555e-2,5.555555555555555e-2]
|
||||
[[]
|
||||
,[]]
|
||||
[[[Para [Str "1"]]
|
||||
,[Para [Str "2"]]]
|
||||
,[[]
|
||||
,[]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Just 5.555555555555555e-2),(AlignDefault,Just 5.555555555555555e-2)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "2"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[]]
|
||||
^D
|
||||
+---+---+
|
||||
| 1 | 2 |
|
||||
|
|
|
@ -5,16 +5,30 @@
|
|||
:header: Flavor,Price,Slogan
|
||||
:file: command/3533-rst-csv-tables.csv
|
||||
^D
|
||||
[Table [Str "Test"] [AlignDefault,AlignDefault,AlignDefault] [0.4,0.2,0.4]
|
||||
[[Plain [Str "Flavor"]]
|
||||
,[Plain [Str "Price"]]
|
||||
,[Plain [Str "Slogan"]]]
|
||||
[[[Plain [Str "Albatross"]]
|
||||
,[Plain [Str "2.99"]]
|
||||
,[Plain [Str "On",Space,Str "a",Space,Str "stick!"]]]
|
||||
,[[Plain [Str "Crunchy",Space,Str "Frog"]]
|
||||
,[Plain [Str "1.49"]]
|
||||
,[Plain [Str "If",Space,Str "we",Space,Str "took",Space,Str "the",Space,Str "bones",Space,Str "out,",Space,Str "it",Space,Str "wouldn't",Space,Str "be",SoftBreak,Str "crunchy,",Space,Str "now",Space,Str "would",Space,Str "it?"]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[Para [Str "Test"]]) [(AlignDefault,Just 0.4),(AlignDefault,Just 0.2),(AlignDefault,Just 0.4)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Flavor"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Price"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Slogan"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Albatross"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "2.99"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "On",Space,Str "a",Space,Str "stick!"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Crunchy",Space,Str "Frog"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1.49"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "If",Space,Str "we",Space,Str "took",Space,Str "the",Space,Str "bones",Space,Str "out,",Space,Str "it",Space,Str "wouldn't",Space,Str "be",SoftBreak,Str "crunchy,",Space,Str "now",Space,Str "would",Space,Str "it?"]]]]
|
||||
[]]
|
||||
```
|
||||
|
||||
```
|
||||
|
@ -28,16 +42,30 @@
|
|||
'cat''s' 3 4
|
||||
'dog''s' 2 3
|
||||
^D
|
||||
[Table [Str "Test"] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[[]
|
||||
,[Plain [Str "a"]]
|
||||
,[Plain [Str "b"]]]
|
||||
[[[Plain [Str "cat's"]]
|
||||
,[Plain [Str "3"]]
|
||||
,[Plain [Str "4"]]]
|
||||
,[[Plain [Str "dog's"]]
|
||||
,[Plain [Str "2"]]
|
||||
,[Plain [Str "3"]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[Para [Str "Test"]]) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "a"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "b"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "cat's"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "3"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "4"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "dog's"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "3"]]]]
|
||||
[]]
|
||||
```
|
||||
|
||||
```
|
||||
|
@ -47,10 +75,18 @@
|
|||
|
||||
"1","\""
|
||||
^D
|
||||
[Table [Str "Test"] [AlignDefault,AlignDefault] [0.0,0.0]
|
||||
[[]
|
||||
,[]]
|
||||
[[[Plain [Str "1"]]
|
||||
,[Plain [Str "\""]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[Para [Str "Test"]]) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "\""]]]]
|
||||
[]]
|
||||
```
|
||||
|
||||
|
|
|
@ -16,15 +16,29 @@ pandoc -f org -t native
|
|||
| 3 | La |
|
||||
^D
|
||||
[Div ("tab",[],[])
|
||||
[Table [Str "Lalelu."] [AlignDefault,AlignDefault] [0.0,0.0]
|
||||
[[Plain [Str "Id"]]
|
||||
,[Plain [Str "Desc"]]]
|
||||
[[[Plain [Str "1"]]
|
||||
,[Plain [Str "La"]]]
|
||||
,[[Plain [Str "2"]]
|
||||
,[Plain [Str "La"]]]
|
||||
,[[Plain [Str "3"]]
|
||||
,[Plain [Str "La"]]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[Para [Str "Lalelu."]]) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Id"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Desc"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "La"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "La"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "3"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "La"]]]]
|
||||
[]]]
|
||||
```
|
||||
|
||||
```
|
||||
|
|
|
@ -5,11 +5,22 @@
|
|||
C & D
|
||||
\end{tabular}
|
||||
^D
|
||||
[Table [] [AlignCenter,AlignCenter] [0.0,0.0]
|
||||
[[]
|
||||
,[]]
|
||||
[[[Plain [Str "A"]]
|
||||
,[Plain [Str "B&1"]]]
|
||||
,[[Plain [Str "C"]]
|
||||
,[Plain [Str "D"]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignCenter,Nothing),(AlignCenter,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "A"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "B&1"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "C"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "D"]]]]
|
||||
[]]
|
||||
```
|
||||
|
|
|
@ -14,11 +14,21 @@
|
|||
Blah & Foo & Bar \\
|
||||
\end{tabular}
|
||||
^D
|
||||
[Table [] [AlignLeft,AlignRight,AlignRight] [0.0,0.0,0.0]
|
||||
[[]
|
||||
,[]
|
||||
,[]]
|
||||
[[[Plain [Str "Blah"]]
|
||||
,[Plain [Str "Foo"]]
|
||||
,[Plain [Str "Bar"]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignLeft,Nothing),(AlignRight,Nothing),(AlignRight,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Blah"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Foo"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Bar"]]]]
|
||||
[]]
|
||||
```
|
||||
|
|
|
@ -8,11 +8,19 @@ pandoc -t native
|
|||
not a caption!
|
||||
::::::::::::::::
|
||||
^D
|
||||
[Table [] [AlignDefault,AlignDefault] [0.0,0.0]
|
||||
[[Plain [Str "col1"]]
|
||||
,[Plain [Str "col2"]]]
|
||||
[[[Plain [Str "1"]]
|
||||
,[Plain [Str "2"]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "col1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "col2"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "2"]]]]
|
||||
[]
|
||||
,Div ("",["notes"],[])
|
||||
[Para [Str "not",Space,Str "a",Space,Str "caption!"]]]
|
||||
```
|
||||
|
|
|
@ -1,11 +1,19 @@
|
|||
```
|
||||
% pandoc -f native -t rst --wrap=none
|
||||
[Table [] [AlignDefault,AlignDefault] [0.3,0.3]
|
||||
[[Plain [Str "one"]]
|
||||
,[Plain [Str "two"]]]
|
||||
[[[Plain [Str "ports"]]
|
||||
,[BlockQuote
|
||||
[Para [Strong [Str "thisIsGoingToBeTooLongAnyway"]]]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Just 0.3),(AlignDefault,Just 0.3)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "one"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "two"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "ports"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[BlockQuote
|
||||
[Para [Strong [Str "thisIsGoingToBeTooLongAnyway"]]]]]]
|
||||
[]]
|
||||
^D
|
||||
+--------------------+-------------------------------------+
|
||||
| one | two |
|
||||
|
|
|
@ -2,8 +2,13 @@
|
|||
% pandoc -f textile -t native
|
||||
|_. heading 1 |_. heading 2|
|
||||
^D
|
||||
[Table [] [AlignDefault,AlignDefault] [0.0,0.0]
|
||||
[[Plain [Str "heading",Space,Str "1"]]
|
||||
,[Plain [Str "heading",Space,Str "2"]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "heading",Space,Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "heading",Space,Str "2"]]]]
|
||||
[]
|
||||
[]]
|
||||
```
|
||||
|
|
|
@ -8,9 +8,17 @@
|
|||
* - spam
|
||||
- ham
|
||||
^D
|
||||
[Table [] [AlignDefault,AlignDefault] [0.0,0.0]
|
||||
[[Plain [Str "Foo"]]
|
||||
,[Plain [Str "Bar"]]]
|
||||
[[[Plain [Str "spam"]]
|
||||
,[Plain [Str "ham"]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Foo"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Bar"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "spam"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "ham"]]]]
|
||||
[]]
|
||||
```
|
||||
|
|
|
@ -13,7 +13,13 @@
|
|||
</tbody>
|
||||
</table>
|
||||
^D
|
||||
[Table [] [AlignDefault] [0.0]
|
||||
[[Plain [Str "Name"]]]
|
||||
[[[Plain [Str "Accounts"]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Name"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Accounts"]]]]
|
||||
[]]
|
||||
```
|
||||
|
|
|
@ -10,7 +10,13 @@
|
|||
</tbody>
|
||||
</table>
|
||||
^D
|
||||
[Table [] [AlignDefault] [0.0]
|
||||
[[]]
|
||||
[[[Plain [Str "Cell"]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell"]]]]
|
||||
[]]
|
||||
```
|
||||
|
|
|
@ -4,9 +4,17 @@
|
|||
| 123456 | :math:`a + b` |
|
||||
+--------+----------------+
|
||||
^D
|
||||
[Table [] [AlignDefault,AlignDefault] [0.125,0.2361111111111111]
|
||||
[[]
|
||||
,[]]
|
||||
[[[Plain [Str "123456"]]
|
||||
,[Plain [Math InlineMath "a + b"]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Just 0.125),(AlignDefault,Just 0.2361111111111111)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123456"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Math InlineMath "a + b"]]]]
|
||||
[]]
|
||||
```
|
||||
|
|
|
@ -7,7 +7,13 @@
|
|||
\end{tabular}
|
||||
\end{document}
|
||||
^D
|
||||
[Table [] [AlignCenter] [0.0]
|
||||
[[]]
|
||||
[[[Plain [Str "d",LineBreak,Str "e"]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignCenter,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "d",LineBreak,Str "e"]]]]
|
||||
[]]
|
||||
```
|
||||
|
|
|
@ -17,16 +17,30 @@ This reference to Figure \ref{fig:label} works fine.
|
|||
^D
|
||||
[Para [Str "This",Space,Str "reference",Space,Str "to",Space,Str "Table",Space,Link ("",[],[("reference-type","ref"),("reference","tbl:label")]) [Str "1"] ("#tbl:label",""),Space,Str "doesn\8217t",Space,Str "work."]
|
||||
,Div ("tbl:label",[],[])
|
||||
[Table [Str "This",Space,Str "caption",Space,Str "has",Space,Str "no",Space,Str "number."] [AlignLeft,AlignCenter,AlignRight] [0.0,0.0,0.0]
|
||||
[[]
|
||||
,[]
|
||||
,[]]
|
||||
[[[Plain [Str "\8212\8212\8211"]]
|
||||
,[Plain [Str "\8212\8212\8211"]]
|
||||
,[Plain [Str "\8212\8212\8211"]]]
|
||||
,[[Plain [Str "\8212\8212\8211"]]
|
||||
,[Plain [Str "\8212\8212\8211"]]
|
||||
,[Plain [Str "\8212\8212\8211"]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[Para [Str "This",Space,Str "caption",Space,Str "has",Space,Str "no",Space,Str "number."]]) [(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignRight,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "\8212\8212\8211"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "\8212\8212\8211"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "\8212\8212\8211"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "\8212\8212\8211"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "\8212\8212\8211"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "\8212\8212\8211"]]]]
|
||||
[]]
|
||||
,Para [Str "This",Space,Str "reference",Space,Str "to",Space,Str "Figure",Space,Link ("",[],[("reference-type","ref"),("reference","fig:label")]) [Str "1"] ("#fig:label",""),Space,Str "works",Space,Str "fine."]
|
||||
,Para [Image ("fig:label",[],[("width","\\textwidth")]) [Str "A",Space,Str "numbered",Space,Str "caption,",Space,Str "if",Space,Str "I",Space,Str "use",Space,Str "pandoc-crossref."] ("example.png","fig:")]]
|
||||
```
|
||||
|
|
|
@ -5,17 +5,35 @@ Apple,25 cents,33
|
|||
"""Navel"" Orange","35 cents",22
|
||||
,,45
|
||||
^D
|
||||
[Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[[Plain [Str "Fruit"]]
|
||||
,[Plain [Str "Price"]]
|
||||
,[Plain [Str "Quantity"]]]
|
||||
[[[Plain [Str "Apple"]]
|
||||
,[Plain [Str "25",Space,Str "cents"]]
|
||||
,[Plain [Str "33"]]]
|
||||
,[[Plain [Str "\"Navel\"",Space,Str "Orange"]]
|
||||
,[Plain [Str "35",Space,Str "cents"]]
|
||||
,[Plain [Str "22"]]]
|
||||
,[[]
|
||||
,[]
|
||||
,[Plain [Str "45"]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Fruit"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Price"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Quantity"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Apple"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "25",Space,Str "cents"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "33"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "\"Navel\"",Space,Str "Orange"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "35",Space,Str "cents"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "22"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "45"]]]]
|
||||
[]]
|
||||
```
|
||||
|
|
|
@ -7,13 +7,24 @@ gfm tests:
|
|||
| apple | 0.13 |
|
||||
| orange|1.12|
|
||||
^D
|
||||
[Table [] [AlignDefault,AlignRight] [0.0,0.0]
|
||||
[[Plain [Str "Fruit"]]
|
||||
,[Plain [Str "Price"]]]
|
||||
[[[Plain [Str "apple"]]
|
||||
,[Plain [Str "0.13"]]]
|
||||
,[[Plain [Str "orange"]]
|
||||
,[Plain [Str "1.12"]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignRight,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Fruit"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Price"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "apple"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "0.13"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "orange"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1.12"]]]]
|
||||
[]]
|
||||
```
|
||||
|
||||
```
|
||||
|
@ -57,13 +68,24 @@ My:thumbsup:emoji:heart:
|
|||
|
||||
```
|
||||
% pandoc -t gfm -f native
|
||||
[Table [Str "The",Space,Str "caption."] [AlignDefault,AlignRight] [0.0,0.0]
|
||||
[[Plain [Str "Fruit"]]
|
||||
,[Plain [Str "Price"]]]
|
||||
[[[Plain [Str "apple"]]
|
||||
,[Plain [Str "0.13"]]]
|
||||
,[[Plain [Str "orange"]]
|
||||
,[Plain [Str "1.12"]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[Para [Str "The",Space,Str "caption."]]) [(AlignDefault,Nothing),(AlignRight,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Fruit"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Price"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "apple"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "0.13"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "orange"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1.12"]]]]
|
||||
[]]
|
||||
^D
|
||||
| Fruit | Price |
|
||||
| ------ | ----: |
|
||||
|
|
|
@ -11,14 +11,28 @@ f & 0.5 & 5,5 \\
|
|||
\bottomrule
|
||||
\end{tabular}
|
||||
^D
|
||||
[Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
|
||||
[[Plain [Math InlineMath ""]]
|
||||
,[Plain [Math InlineMath "f1"]]
|
||||
,[Plain [Math InlineMath "f2"]]]
|
||||
[[[Plain [Math InlineMath "e"]]
|
||||
,[Plain [Math InlineMath "0.5"]]
|
||||
,[Plain [Math InlineMath "4"]]]
|
||||
,[[Plain [Math InlineMath "f"]]
|
||||
,[Plain [Math InlineMath "0.5"]]
|
||||
,[Plain [Math InlineMath "5,5"]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Math InlineMath ""]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Math InlineMath "f1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Math InlineMath "f2"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Math InlineMath "e"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Math InlineMath "0.5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Math InlineMath "4"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Math InlineMath "f"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Math InlineMath "0.5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Math InlineMath "5,5"]]]]
|
||||
[]]
|
||||
```
|
||||
|
|
|
@ -6,33 +6,51 @@
|
|||
& Column Heading 2
|
||||
& Column Heading 3 \\
|
||||
\hline
|
||||
Cell 1.1
|
||||
Cell 1.1
|
||||
& Cell 1.2
|
||||
& Cell 1.3 \\
|
||||
\hline
|
||||
Cell 2.1
|
||||
Cell 2.1
|
||||
& Cell 2.2
|
||||
& Cell 2.3 \\
|
||||
\hline
|
||||
Cell 3.1
|
||||
Cell 3.1
|
||||
& Cell 3.2
|
||||
& Cell 3.3 \\
|
||||
\hline
|
||||
\end{tabularx}
|
||||
^D
|
||||
[Table [] [AlignCenter,AlignCenter,AlignCenter] [0.0,0.0,0.0]
|
||||
[[Plain [Str "Column",Space,Str "Heading",Space,Str "1"]]
|
||||
,[Plain [Str "Column",Space,Str "Heading",Space,Str "2"]]
|
||||
,[Plain [Str "Column",Space,Str "Heading",Space,Str "3"]]]
|
||||
[[[Plain [Str "Cell",Space,Str "1.1"]]
|
||||
,[Plain [Str "Cell",Space,Str "1.2"]]
|
||||
,[Plain [Str "Cell",Space,Str "1.3"]]]
|
||||
,[[Plain [Str "Cell",Space,Str "2.1"]]
|
||||
,[Plain [Str "Cell",Space,Str "2.2"]]
|
||||
,[Plain [Str "Cell",Space,Str "2.3"]]]
|
||||
,[[Plain [Str "Cell",Space,Str "3.1"]]
|
||||
,[Plain [Str "Cell",Space,Str "3.2"]]
|
||||
,[Plain [Str "Cell",Space,Str "3.3"]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignCenter,Nothing),(AlignCenter,Nothing),(AlignCenter,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Column",Space,Str "Heading",Space,Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Column",Space,Str "Heading",Space,Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Column",Space,Str "Heading",Space,Str "3"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "1.1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "1.2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "1.3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "2.1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "2.2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "2.3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "3.1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "3.2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "3.3"]]]]
|
||||
[]]
|
||||
```
|
||||
|
||||
```
|
||||
|
@ -43,33 +61,51 @@
|
|||
& Column Heading 2
|
||||
& Column Heading 3 \\
|
||||
\hline
|
||||
Cell 1.1
|
||||
Cell 1.1
|
||||
& Cell 1.2
|
||||
& Cell 1.3 \\
|
||||
\hline
|
||||
Cell 2.1
|
||||
Cell 2.1
|
||||
& Cell 2.2
|
||||
& Cell 2.3 \\
|
||||
\hline
|
||||
Cell 3.1
|
||||
Cell 3.1
|
||||
& Cell 3.2
|
||||
& Cell 3.3 \\
|
||||
\hline
|
||||
\end{tabularx}
|
||||
^D
|
||||
[Table [] [AlignLeft,AlignCenter,AlignLeft] [0.0,0.0,0.25]
|
||||
[[Plain [Str "Column",Space,Str "Heading",Space,Str "1"]]
|
||||
,[Plain [Str "Column",Space,Str "Heading",Space,Str "2"]]
|
||||
,[Plain [Str "Column",Space,Str "Heading",Space,Str "3"]]]
|
||||
[[[Plain [Str "Cell",Space,Str "1.1"]]
|
||||
,[Plain [Str "Cell",Space,Str "1.2"]]
|
||||
,[Plain [Str "Cell",Space,Str "1.3"]]]
|
||||
,[[Plain [Str "Cell",Space,Str "2.1"]]
|
||||
,[Plain [Str "Cell",Space,Str "2.2"]]
|
||||
,[Plain [Str "Cell",Space,Str "2.3"]]]
|
||||
,[[Plain [Str "Cell",Space,Str "3.1"]]
|
||||
,[Plain [Str "Cell",Space,Str "3.2"]]
|
||||
,[Plain [Str "Cell",Space,Str "3.3"]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignLeft,Just 0.25)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Column",Space,Str "Heading",Space,Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Column",Space,Str "Heading",Space,Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Column",Space,Str "Heading",Space,Str "3"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "1.1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "1.2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "1.3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "2.1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "2.2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "2.3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "3.1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "3.2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "3.3"]]]]
|
||||
[]]
|
||||
```
|
||||
|
||||
```
|
||||
|
@ -80,31 +116,49 @@
|
|||
& Column Heading 2
|
||||
& Column Heading 3 \\
|
||||
\hline
|
||||
Cell 1.1
|
||||
Cell 1.1
|
||||
& Cell 1.2
|
||||
& Cell 1.3 \\
|
||||
\hline
|
||||
Cell 2.1
|
||||
Cell 2.1
|
||||
& Cell 2.2
|
||||
& Cell 2.3 \\
|
||||
\hline
|
||||
Cell 3.1
|
||||
Cell 3.1
|
||||
& Cell 3.2
|
||||
& Cell 3.3 \\
|
||||
\hline
|
||||
\end{tabularx}
|
||||
^D
|
||||
[Table [] [AlignLeft,AlignCenter,AlignLeft] [0.25,0.0,0.25]
|
||||
[[Plain [Str "Column",Space,Str "Heading",Space,Str "1"]]
|
||||
,[Plain [Str "Column",Space,Str "Heading",Space,Str "2"]]
|
||||
,[Plain [Str "Column",Space,Str "Heading",Space,Str "3"]]]
|
||||
[[[Plain [Str "Cell",Space,Str "1.1"]]
|
||||
,[Plain [Str "Cell",Space,Str "1.2"]]
|
||||
,[Plain [Str "Cell",Space,Str "1.3"]]]
|
||||
,[[Plain [Str "Cell",Space,Str "2.1"]]
|
||||
,[Plain [Str "Cell",Space,Str "2.2"]]
|
||||
,[Plain [Str "Cell",Space,Str "2.3"]]]
|
||||
,[[Plain [Str "Cell",Space,Str "3.1"]]
|
||||
,[Plain [Str "Cell",Space,Str "3.2"]]
|
||||
,[Plain [Str "Cell",Space,Str "3.3"]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignLeft,Just 0.25),(AlignCenter,Nothing),(AlignLeft,Just 0.25)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Column",Space,Str "Heading",Space,Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Column",Space,Str "Heading",Space,Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Column",Space,Str "Heading",Space,Str "3"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "1.1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "1.2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "1.3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "2.1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "2.2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "2.3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "3.1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "3.2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "3.3"]]]]
|
||||
[]]
|
||||
```
|
||||
|
|
|
@ -69,25 +69,50 @@ Pandoc (Meta {unMeta = fromList []})
|
|||
,Para [Image ("",[],[]) [Str "here is a red flower"] ("Red-Flower.jpg","")]
|
||||
,Header 3 ("",[],[]) [Str "Creole 0.4"]
|
||||
,Para [Str "Tables",Space,Str "are",Space,Str "done",Space,Str "like",Space,Str "this:"]
|
||||
,Table [] [AlignDefault,AlignDefault] [0.0,0.0]
|
||||
[[Plain [Str "header",Space,Str "col1"]]
|
||||
,[Plain [Str "header",Space,Str "col2"]]]
|
||||
[[[Plain [Str "col1"]]
|
||||
,[Plain [Str "col2"]]]
|
||||
,[[Plain [Str "you"]]
|
||||
,[Plain [Str "can"]]]
|
||||
,[[Plain [Str "also"]]
|
||||
,[Plain [Str "align",LineBreak,Str "it."]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "header",Space,Str "col1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "header",Space,Str "col2"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "col1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "col2"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "you"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "can"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "also"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "align",LineBreak,Str "it."]]]]
|
||||
[]
|
||||
,Para [Str "You",Space,Str "can",Space,Str "format",Space,Str "an",Space,Str "address",Space,Str "by",Space,Str "simply",Space,Str "forcing",Space,Str "linebreaks:"]
|
||||
,Para [Str "My",Space,Str "contact",Space,Str "dates:",LineBreak,Str "Pone:",Space,Str "xyz",LineBreak,Str "Fax:",Space,Str "+45",LineBreak,Str "Mobile:",Space,Str "abc"]
|
||||
,Header 3 ("",[],[]) [Str "Creole 0.5"]
|
||||
,Table [] [AlignDefault,AlignDefault] [0.0,0.0]
|
||||
[[Plain [Str "Header",Space,Str "title"]]
|
||||
,[Plain [Str "Another",Space,Str "header",Space,Str "title"]]]
|
||||
[[[Plain [Code ("",[],[]) " //not italic text// "]]
|
||||
,[Plain [Code ("",[],[]) " **not bold text** "]]]
|
||||
,[[Plain [Emph [Str "italic",Space,Str "text"]]]
|
||||
,[Plain [Strong [Space,Str "bold",Space,Str "text",Space]]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Header",Space,Str "title"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Another",Space,Str "header",Space,Str "title"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Code ("",[],[]) " //not italic text// "]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Code ("",[],[]) " **not bold text** "]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Emph [Str "italic",Space,Str "text"]]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Strong [Space,Str "bold",Space,Str "text",Space]]]]]
|
||||
[]
|
||||
,Header 3 ("",[],[]) [Str "Creole 1.0"]
|
||||
,Para [Str "If",Space,Str "interwiki",Space,Str "links",Space,Str "are",Space,Str "setup",Space,Str "in",Space,Str "your",Space,Str "wiki,",Space,Str "this",Space,Str "links",Space,Str "to",Space,Str "the",Space,Str "WikiCreole",Space,Str "page",Space,Str "about",Space,Str "Creole",Space,Str "1.0",Space,Str "test",Space,Str "cases:",Space,Link ("",[],[]) [Str "WikiCreole:Creole1.0TestCases"] ("WikiCreole:Creole1.0TestCases",""),Str "."]
|
||||
,HorizontalRule
|
||||
|
|
|
@ -282,116 +282,255 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Sof
|
|||
,Para [Str "This",Space,Str "paragraph",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "part",Space,Str "of",Space,Str "the",Space,Str "note,",Space,Str "as",Space,Str "it",Space,Str "is",Space,Str "not",Space,Str "indented."]
|
||||
,Header 1 ("tables",[],[]) [Str "Tables"]
|
||||
,Para [Str "Simple",Space,Str "table",Space,Str "with",Space,Str "caption:"]
|
||||
,Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."] [AlignRight,AlignLeft,AlignCenter,AlignLeft] [0.0,0.0,0.0,0.0]
|
||||
[[Plain [Str "Right"]]
|
||||
,[Plain [Str "Left"]]
|
||||
,[Plain [Str "Center"]]
|
||||
,[Plain [Str "Default"]]]
|
||||
[[[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]]
|
||||
,[[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]]
|
||||
,[[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[Para [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."]]) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignLeft,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Right"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Left"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Center"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Default"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]]]
|
||||
[]
|
||||
,Para [Str "Simple",Space,Str "table",Space,Str "without",Space,Str "caption:"]
|
||||
,Table [] [AlignRight,AlignLeft,AlignCenter,AlignLeft] [0.0,0.0,0.0,0.0]
|
||||
[[Plain [Str "Right"]]
|
||||
,[Plain [Str "Left"]]
|
||||
,[Plain [Str "Center"]]
|
||||
,[Plain [Str "Default"]]]
|
||||
[[[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]]
|
||||
,[[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]]
|
||||
,[[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignLeft,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Right"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Left"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Center"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Default"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]]]
|
||||
[]
|
||||
,Para [Str "Simple",Space,Str "table",Space,Str "indented",Space,Str "two",Space,Str "spaces:"]
|
||||
,Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."] [AlignRight,AlignLeft,AlignCenter,AlignLeft] [0.0,0.0,0.0,0.0]
|
||||
[[Plain [Str "Right"]]
|
||||
,[Plain [Str "Left"]]
|
||||
,[Plain [Str "Center"]]
|
||||
,[Plain [Str "Default"]]]
|
||||
[[[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]]
|
||||
,[[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]]
|
||||
,[[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[Para [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."]]) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignLeft,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Right"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Left"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Center"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Default"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]]]
|
||||
[]
|
||||
,Para [Str "Multiline",Space,Str "table",Space,Str "with",Space,Str "caption:"]
|
||||
,Table [Str "Here's",Space,Str "the",Space,Str "caption.",Space,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.2,0.2,0.3,0.3]
|
||||
[[Plain [Str "Centered",Space,Str "Header"]]
|
||||
,[Plain [Str "Left",Space,Str "Aligned"]]
|
||||
,[Plain [Str "Right",Space,Str "Aligned"]]
|
||||
,[Plain [Str "Default",Space,Str "aligned"]]]
|
||||
[[[Plain [Str "First"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "12.0"]]
|
||||
,[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines."]]]
|
||||
,[[Plain [Str "Second"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "5.0"]]
|
||||
,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[Para [Str "Here's",Space,Str "the",Space,Str "caption.",Space,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."]]) [(AlignCenter,Just 0.2),(AlignLeft,Just 0.2),(AlignRight,Just 0.3),(AlignLeft,Just 0.3)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Centered",Space,Str "Header"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Left",Space,Str "Aligned"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Right",Space,Str "Aligned"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Default",Space,Str "aligned"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "First"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "row"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12.0"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines."]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Second"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "row"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "5.0"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]]
|
||||
[]
|
||||
,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "caption:"]
|
||||
,Table [] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.1,0.2,0.3,0.4]
|
||||
[[Plain [Str "Centered",Space,Str "Header"]]
|
||||
,[Plain [Str "Left",Space,Str "Aligned"]]
|
||||
,[Plain [Str "Right",Space,Str "Aligned"]]
|
||||
,[Plain [Str "Default",Space,Str "aligned"]]]
|
||||
[[[Plain [Str "First"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "12.0"]]
|
||||
,[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines."]]]
|
||||
,[[Plain [Str "Second"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "5.0"]]
|
||||
,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignCenter,Just 0.1),(AlignLeft,Just 0.2),(AlignRight,Just 0.3),(AlignLeft,Just 0.4)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Centered",Space,Str "Header"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Left",Space,Str "Aligned"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Right",Space,Str "Aligned"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Default",Space,Str "aligned"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "First"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "row"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12.0"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines."]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Second"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "row"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "5.0"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]]
|
||||
[]
|
||||
,Para [Str "Table",Space,Str "without",Space,Str "column",Space,Str "headers:"]
|
||||
,Table [] [AlignRight,AlignLeft,AlignCenter,AlignRight] [0.0,0.0,0.0,0.0]
|
||||
[[]
|
||||
,[]
|
||||
,[]
|
||||
,[]]
|
||||
[[[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]]
|
||||
,[[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]]
|
||||
,[[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignRight,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]]]
|
||||
[]
|
||||
,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "column",Space,Str "headers:"]
|
||||
,Table [] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.25,0.25,0.25,0.25]
|
||||
[[]
|
||||
,[]
|
||||
,[]
|
||||
,[]]
|
||||
[[[Plain [Str "First"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "12.0"]]
|
||||
,[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines."]]]
|
||||
,[[Plain [Str "Second"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "5.0"]]
|
||||
,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignCenter,Just 0.25),(AlignLeft,Just 0.25),(AlignRight,Just 0.25),(AlignLeft,Just 0.25)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "First"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "row"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12.0"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines."]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Second"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "row"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "5.0"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]]
|
||||
[]]
|
||||
|
|
|
@ -1,15 +1,39 @@
|
|||
[Table [] [AlignDefault] [0.0]
|
||||
[[]]
|
||||
[[[]]
|
||||
,[[Plain [Str "User\8217s",Space,Str "Guide"]]]
|
||||
,[[]]
|
||||
,[[]]
|
||||
,[[]]
|
||||
,[[Plain [Str "11",Space,Str "August",Space,Str "2017"]]]
|
||||
,[[]]
|
||||
,[[]]
|
||||
,[[]]
|
||||
,[[]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "User\8217s",Space,Str "Guide"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "11",Space,Str "August",Space,Str "2017"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[]
|
||||
,Para [Str "CONTENTS"]
|
||||
,Para [Strong [Str "Section",Space,Str "Page"]]
|
||||
,Para [Str "FIGURES",Space,Str "iv"]
|
||||
|
|
|
@ -1,10 +1,24 @@
|
|||
[Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[[]
|
||||
,[]
|
||||
,[]]
|
||||
[[[Plain [Strong [Str "col1Header"]]]
|
||||
,[Plain [Strong [Str "col2Header"]]]
|
||||
,[Plain [Strong [Str "col3Header"]]]]
|
||||
,[[Plain [Str "col1",Space,Str "content"]]
|
||||
,[Plain [Str "Body",Space,Str "copy"]]
|
||||
,[Plain [Str "col3",Space,Str "content"]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Strong [Str "col1Header"]]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Strong [Str "col2Header"]]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Strong [Str "col3Header"]]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "col1",Space,Str "content"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Body",Space,Str "copy"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "col3",Space,Str "content"]]]]
|
||||
[]]
|
||||
|
|
|
@ -1,7 +1,17 @@
|
|||
[Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[[]
|
||||
,[]
|
||||
,[]]
|
||||
[[[Plain [Str "One"]]
|
||||
,[Plain [Str "Row"]]
|
||||
,[Plain [Str "Table"]]]]]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "One"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Row"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Table"]]]]
|
||||
[]]
|
||||
|
|
|
@ -1,16 +1,37 @@
|
|||
[Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0,0.0,0.0]
|
||||
[[]
|
||||
,[]
|
||||
,[Plain [Str "h3"]]
|
||||
,[Plain [Str "h4"]]
|
||||
,[Plain [Str "h5"]]]
|
||||
[[[Plain [Str "c11"]]
|
||||
,[]
|
||||
,[]
|
||||
,[]
|
||||
,[]]
|
||||
,[[]
|
||||
,[Plain [Str "c22"]]
|
||||
,[Plain [Str "c23"]]
|
||||
,[]
|
||||
,[]]]]
|
||||
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "h3"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "h4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "h5"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "c11"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "c22"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "c23"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[]]
|
|
@ -1,11 +1,19 @@
|
|||
[Table [] [AlignDefault,AlignDefault] [0.0,0.0]
|
||||
[[Plain [Str "Cell",Space,Str "with",Space,Str "text"]]
|
||||
,[Plain [Str "Cell",Space,Str "with",Space,Str "text"]]]
|
||||
[[[BulletList
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "with",Space,Str "text"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cell",Space,Str "with",Space,Str "text"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[BulletList
|
||||
[[Para [Str "Cell",Space,Str "with"]]
|
||||
,[Para [Str "A"]]
|
||||
,[Para [Str "Bullet",Space,Str "list"]]]]
|
||||
,[OrderedList (1,Decimal,Period)
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[OrderedList (1,Decimal,Period)
|
||||
[[Para [Str "Cell",Space,Str "with"]]
|
||||
,[Para [Str "A"]]
|
||||
,[Para [Str "Numbered",Space,Str "list."]]]]]]]
|
||||
,[Para [Str "Numbered",Space,Str "list."]]]]]]
|
||||
[]]
|
||||
|
|
|
@ -1,36 +1,80 @@
|
|||
[Header 2 ("a-table-with-and-without-a-header-row",[],[]) [Str "A",Space,Str "table,",Space,Str "with",Space,Str "and",Space,Str "without",Space,Str "a",Space,Str "header",Space,Str "row"]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0,0.0]
|
||||
[[Plain [Str "Name"]]
|
||||
,[Plain [Str "Game"]]
|
||||
,[Plain [Str "Fame"]]
|
||||
,[Plain [Str "Blame"]]]
|
||||
[[[Plain [Str "Lebron",Space,Str "James"]]
|
||||
,[Plain [Str "Basketball"]]
|
||||
,[Plain [Str "Very",Space,Str "High"]]
|
||||
,[Plain [Str "Leaving",Space,Str "Cleveland"]]]
|
||||
,[[Plain [Str "Ryan",Space,Str "Braun"]]
|
||||
,[Plain [Str "Baseball"]]
|
||||
,[Plain [Str "Moderate"]]
|
||||
,[Plain [Str "Steroids"]]]
|
||||
,[[Plain [Str "Russell",Space,Str "Wilson"]]
|
||||
,[Plain [Str "Football"]]
|
||||
,[Plain [Str "High"]]
|
||||
,[Plain [Str "Tacky",Space,Str "uniform"]]]]
|
||||
,Table [] [AlignDefault,AlignDefault] [0.0,0.0]
|
||||
[[]
|
||||
,[]]
|
||||
[[[Plain [Str "Sinple"]]
|
||||
,[Plain [Str "Table"]]]
|
||||
,[[Plain [Str "Without"]]
|
||||
,[Plain [Str "Header"]]]]
|
||||
,Table [] [AlignDefault,AlignDefault] [0.0,0.0]
|
||||
[[]
|
||||
,[]]
|
||||
[[[Para [Str "Simple"]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Name"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Game"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Fame"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Blame"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Lebron",Space,Str "James"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Basketball"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Very",Space,Str "High"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Leaving",Space,Str "Cleveland"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Ryan",Space,Str "Braun"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Baseball"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Moderate"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Steroids"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Russell",Space,Str "Wilson"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Football"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "High"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Tacky",Space,Str "uniform"]]]]
|
||||
[]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Sinple"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Table"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Without"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Header"]]]]
|
||||
[]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Simple"]
|
||||
,Para [Str "Multiparagraph"]]
|
||||
,[Para [Str "Table"]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Table"]
|
||||
,Para [Str "Full"]]]
|
||||
,[[Para [Str "Of"]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Of"]
|
||||
,Para [Str "Paragraphs"]]
|
||||
,[Para [Str "In",Space,Str "each"]
|
||||
,Para [Str "Cell."]]]]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "In",Space,Str "each"]
|
||||
,Para [Str "Cell."]]]]
|
||||
[]]
|
||||
|
|
|
@ -1,18 +1,34 @@
|
|||
[Table [Str "Sample",Space,Str "grid",Space,Str "table."] [AlignDefault,AlignDefault,AlignDefault] [0.2222222222222222,0.2222222222222222,0.2916666666666667]
|
||||
[[Plain [Str "Fruit"]]
|
||||
,[Plain [Str "Price"]]
|
||||
,[Plain [Str "Advantages"]]]
|
||||
[[[Para [Str "Bananas"]]
|
||||
,[Para [Str "$1.34"]]
|
||||
,[Para [Str "built-in",Space,Str "wrapper"]
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[Para [Str "Sample",Space,Str "grid",Space,Str "table."]]) [(AlignDefault,Just 0.2222222222222222),(AlignDefault,Just 0.2222222222222222),(AlignDefault,Just 0.2916666666666667)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Fruit"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Price"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Advantages"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Bananas"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "$1.34"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "built-in",Space,Str "wrapper"]
|
||||
,Para [Str "potassium"]]]
|
||||
,[[Para [Str "Oranges"]]
|
||||
,[Para [Str "$2.10"]]
|
||||
,[BulletList
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Oranges"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "$2.10"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[BulletList
|
||||
[[Plain [Str "cures",Space,Str "scurvy"]]
|
||||
,[Plain [Str "tasty"]]]]]
|
||||
,[[Para [Str "Apples"]]
|
||||
,[Para [Str "$1.10"]]
|
||||
,[Para [Str "Some",Space,Str "text",LineBreak,LineBreak,Str "after",Space,Str "two",Space,Str "linebreaks"]
|
||||
]]
|
||||
]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Apples"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "$1.10"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Some",Space,Str "text",LineBreak,LineBreak,Str "after",Space,Str "two",Space,Str "linebreaks"]]]]
|
||||
[]]
|
||||
|
|
|
@ -331,147 +331,329 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl
|
|||
,Para [Emph [Str "Trailing",Space,Str "spaces"],Space,Str "text"]
|
||||
,Header 1 ("tables",[],[]) [Str "Tables"]
|
||||
,Header 2 ("tables-with-headers",[],[]) [Str "Tables",Space,Str "with",Space,Str "Headers"]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[[Plain [Str "X"]]
|
||||
,[Plain [Str "Y"]]
|
||||
,[Plain [Str "Z"]]]
|
||||
[[[Plain [Str "1"]]
|
||||
,[Plain [Str "2"]]
|
||||
,[Plain [Str "3"]]]
|
||||
,[[Plain [Str "4"]]
|
||||
,[Plain [Str "5"]]
|
||||
,[Plain [Str "6"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "X"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Y"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Z"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "6"]]]]
|
||||
[]
|
||||
,HorizontalRule
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[[Plain [Str "X"]]
|
||||
,[Plain [Str "Y"]]
|
||||
,[Plain [Str "Z"]]]
|
||||
[[[Plain [Str "1"]]
|
||||
,[Plain [Str "2"]]
|
||||
,[Plain [Str "3"]]]
|
||||
,[[Plain [Str "4"]]
|
||||
,[Plain [Str "5"]]
|
||||
,[Plain [Str "6"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "X"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Y"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Z"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "6"]]]]
|
||||
[]
|
||||
,HorizontalRule
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[[Plain [Str "X"]]
|
||||
,[Plain [Str "Y"]]
|
||||
,[Plain [Str "Z"]]]
|
||||
[[[Plain [Str "1"]]
|
||||
,[Plain [Str "2"]]
|
||||
,[Plain [Str "3"]]]
|
||||
,[[Plain [Str "4"]]
|
||||
,[Plain [Str "5"]]
|
||||
,[Plain [Str "6"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "X"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Y"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Z"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "6"]]]]
|
||||
[]
|
||||
,HorizontalRule
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[[Plain [Str "X"]]
|
||||
,[Plain [Str "Y"]]
|
||||
,[Plain [Str "Z"]]]
|
||||
[[[Plain [Str "1"]]
|
||||
,[Plain [Str "2"]]
|
||||
,[Plain [Str "3"]]]
|
||||
,[[Plain [Str "4"]]
|
||||
,[Plain [Str "5"]]
|
||||
,[Plain [Str "6"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "X"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Y"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Z"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "6"]]]]
|
||||
[]
|
||||
,HorizontalRule
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[[Plain [Str "X"]]
|
||||
,[Plain [Str "Y"]]
|
||||
,[Plain [Str "Z"]]]
|
||||
[[[Plain [Str "1"]]
|
||||
,[Plain [Str "2"]]
|
||||
,[Plain [Str "3"]]]
|
||||
,[[Plain [Str "4"]]
|
||||
,[Plain [Str "5"]]
|
||||
,[Plain [Str "6"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "X"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Y"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Z"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "6"]]]]
|
||||
[]
|
||||
,HorizontalRule
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[[Plain [Str "X"]]
|
||||
,[Plain [Str "Y"]]
|
||||
,[Plain [Str "Z"]]]
|
||||
[[[Plain [Str "1"]]
|
||||
,[Plain [Str "2"]]
|
||||
,[Plain [Str "3"]]]
|
||||
,[[Plain [Str "4"]]
|
||||
,[Plain [Str "5"]]
|
||||
,[Plain [Str "6"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "X"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Y"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Z"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "6"]]]]
|
||||
[]
|
||||
,HorizontalRule
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[[Plain [Str "X"]]
|
||||
,[Plain [Str "Y"]]
|
||||
,[Plain [Str "Z"]]]
|
||||
[[[Plain [Str "1"]]
|
||||
,[Plain [Str "2"]]
|
||||
,[Plain [Str "3"]]]
|
||||
,[[Plain [Str "4"]]
|
||||
,[Plain [Str "5"]]
|
||||
,[Plain [Str "6"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "X"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Y"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Z"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "6"]]]]
|
||||
[]
|
||||
,HorizontalRule
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[[Plain [Str "X"]]
|
||||
,[Plain [Str "Y"]]
|
||||
,[Plain [Str "Z"]]]
|
||||
[[[Plain [Str "1"]]
|
||||
,[Plain [Str "2"]]
|
||||
,[Plain [Str "3"]]]
|
||||
,[[Plain [Str "4"]]
|
||||
,[Plain [Str "5"]]
|
||||
,[Plain [Str "6"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "X"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Y"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Z"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "6"]]]]
|
||||
[]
|
||||
,HorizontalRule
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[[Plain [Str "X"]]
|
||||
,[Plain [Str "Y"]]
|
||||
,[Plain [Str "Z"]]]
|
||||
[[[Plain [Str "1"]]
|
||||
,[Para [Str "2"]]
|
||||
,[Plain [Str "3"]]]
|
||||
,[[Plain [Str "4"]]
|
||||
,[Plain [Str "5"]]
|
||||
,[Plain [Str "6"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "X"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Y"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Z"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "6"]]]]
|
||||
[]
|
||||
,Header 2 ("tables-without-headers",[],[]) [Str "Tables",Space,Str "without",Space,Str "Headers"]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[[]
|
||||
,[]
|
||||
,[]]
|
||||
[[[Plain [Str "1"]]
|
||||
,[Plain [Str "2"]]
|
||||
,[Plain [Str "3"]]]
|
||||
,[[Plain [Str "4"]]
|
||||
,[Plain [Str "5"]]
|
||||
,[Plain [Str "6"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "6"]]]]
|
||||
[]
|
||||
,HorizontalRule
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[[]
|
||||
,[]
|
||||
,[]]
|
||||
[[[Plain [Str "1"]]
|
||||
,[Plain [Str "2"]]
|
||||
,[Plain [Str "3"]]]
|
||||
,[[Plain [Str "4"]]
|
||||
,[Plain [Str "5"]]
|
||||
,[Plain [Str "6"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "6"]]]]
|
||||
[]
|
||||
,HorizontalRule
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[[]
|
||||
,[]
|
||||
,[]]
|
||||
[[[Plain [Str "1"]]
|
||||
,[Plain [Str "2"]]
|
||||
,[Plain [Str "3"]]]
|
||||
,[[Plain [Str "4"]]
|
||||
,[Plain [Str "5"]]
|
||||
,[Plain [Str "6"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "6"]]]]
|
||||
[]
|
||||
,HorizontalRule
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[[]
|
||||
,[]
|
||||
,[]]
|
||||
[[[Plain [Str "1"]]
|
||||
,[Plain [Str "2"]]
|
||||
,[Plain [Str "3"]]]
|
||||
,[[Plain [Str "4"]]
|
||||
,[Plain [Str "5"]]
|
||||
,[Plain [Str "6"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "6"]]]]
|
||||
[]
|
||||
,Header 2 ("empty-tables",[],[]) [Str "Empty",Space,Str "Tables"]
|
||||
,Para [Str "This",Space,Str "section",Space,Str "should",Space,Str "be",Space,Str "empty."]]
|
||||
|
|
|
@ -287,136 +287,318 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
,Para [Emph [Str "Trailing",Space,Str "spaces"],Space,Str "text"]
|
||||
,Header 1 ("tables",[],[]) [Str "Tables"]
|
||||
,Header 2 ("tables-with-headers",[],[]) [Str "Tables",Space,Str "with",Space,Str "Headers"]
|
||||
,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
|
||||
[[Para [Str "X"]]
|
||||
,[Para [Str "Y"]]
|
||||
,[Para [Str "Z"]]]
|
||||
[[[Para [Str "1"]]
|
||||
,[Para [Str "2"]]
|
||||
,[Para [Str "3"]]]
|
||||
,[[Para [Str "4"]]
|
||||
,[Para [Str "5"]]
|
||||
,[Para [Str "6"]]]]
|
||||
,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
|
||||
[[Para [Str "X"]]
|
||||
,[Para [Str "Y"]]
|
||||
,[Para [Str "Z"]]]
|
||||
[[[Para [Str "1"]]
|
||||
,[Para [Str "2"]]
|
||||
,[Para [Str "3"]]]
|
||||
,[[Para [Str "4"]]
|
||||
,[Para [Str "5"]]
|
||||
,[Para [Str "6"]]]]
|
||||
,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
|
||||
[[Para [Str "X"]]
|
||||
,[Para [Str "Y"]]
|
||||
,[Para [Str "Z"]]]
|
||||
[[[Para [Str "1"]]
|
||||
,[Para [Str "2"]]
|
||||
,[Para [Str "3"]]]
|
||||
,[[Para [Str "4"]]
|
||||
,[Para [Str "5"]]
|
||||
,[Para [Str "6"]]]]
|
||||
,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
|
||||
[[Para [Str "X"]]
|
||||
,[Para [Str "Y"]]
|
||||
,[Para [Str "Z"]]]
|
||||
[[[Para [Str "1"]]
|
||||
,[Para [Str "2"]]
|
||||
,[Para [Str "3"]]]
|
||||
,[[Para [Str "4"]]
|
||||
,[Para [Str "5"]]
|
||||
,[Para [Str "6"]]]]
|
||||
,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
|
||||
[[Para [Str "X"]]
|
||||
,[Para [Str "Y"]]
|
||||
,[Para [Str "Z"]]]
|
||||
[[[Para [Str "1"]]
|
||||
,[Para [Str "2"]]
|
||||
,[Para [Str "3"]]]
|
||||
,[[Para [Str "4"]]
|
||||
,[Para [Str "5"]]
|
||||
,[Para [Str "6"]]]]
|
||||
,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
|
||||
[[Para [Str "X"]]
|
||||
,[Para [Str "Y"]]
|
||||
,[Para [Str "Z"]]]
|
||||
[[[Para [Str "1"]]
|
||||
,[Para [Str "2"]]
|
||||
,[Para [Str "3"]]]
|
||||
,[[Para [Str "4"]]
|
||||
,[Para [Str "5"]]
|
||||
,[Para [Str "6"]]]]
|
||||
,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
|
||||
[[Para [Str "X"]]
|
||||
,[Para [Str "Y"]]
|
||||
,[Para [Str "Z"]]]
|
||||
[[[Para [Str "1"]]
|
||||
,[Para [Str "2"]]
|
||||
,[Para [Str "3"]]]
|
||||
,[[Para [Str "4"]]
|
||||
,[Para [Str "5"]]
|
||||
,[Para [Str "6"]]]]
|
||||
,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
|
||||
[[Para [Str "X"]]
|
||||
,[Para [Str "Y"]]
|
||||
,[Para [Str "Z"]]]
|
||||
[[[Para [Str "1"]]
|
||||
,[Para [Str "2"]]
|
||||
,[Para [Str "3"]]]
|
||||
,[[Para [Str "4"]]
|
||||
,[Para [Str "5"]]
|
||||
,[Para [Str "6"]]]]
|
||||
,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
|
||||
[[Para [Str "X"]]
|
||||
,[Para [Str "Y"]]
|
||||
,[Para [Str "Z"]]]
|
||||
[[[Para [Str "1"]]
|
||||
,[Para [Str "2"]]
|
||||
,[Para [Str "3"]]]
|
||||
,[[Para [Str "4"]]
|
||||
,[Para [Str "5"]]
|
||||
,[Para [Str "6"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "X"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Y"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Z"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "6"]]]]
|
||||
[]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "X"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Y"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Z"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "6"]]]]
|
||||
[]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "X"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Y"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Z"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "6"]]]]
|
||||
[]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "X"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Y"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Z"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "6"]]]]
|
||||
[]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "X"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Y"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Z"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "6"]]]]
|
||||
[]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "X"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Y"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Z"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "6"]]]]
|
||||
[]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "X"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Y"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Z"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "6"]]]]
|
||||
[]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "X"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Y"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Z"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "6"]]]]
|
||||
[]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "X"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Y"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Z"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "6"]]]]
|
||||
[]
|
||||
,Header 2 ("tables-without-headers",[],[]) [Str "Tables",Space,Str "without",Space,Str "Headers"]
|
||||
,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
|
||||
[[]
|
||||
,[]
|
||||
,[]]
|
||||
[[[Para [Str "1"]]
|
||||
,[Para [Str "2"]]
|
||||
,[Para [Str "3"]]]
|
||||
,[[Para [Str "4"]]
|
||||
,[Para [Str "5"]]
|
||||
,[Para [Str "6"]]]]
|
||||
,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
|
||||
[[]
|
||||
,[]
|
||||
,[]]
|
||||
[[[Para [Str "1"]]
|
||||
,[Para [Str "2"]]
|
||||
,[Para [Str "3"]]]
|
||||
,[[Para [Str "4"]]
|
||||
,[Para [Str "5"]]
|
||||
,[Para [Str "6"]]]]
|
||||
,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
|
||||
[[]
|
||||
,[]
|
||||
,[]]
|
||||
[[[Para [Str "1"]]
|
||||
,[Para [Str "2"]]
|
||||
,[Para [Str "3"]]]
|
||||
,[[Para [Str "4"]]
|
||||
,[Para [Str "5"]]
|
||||
,[Para [Str "6"]]]]
|
||||
,Table [] [AlignLeft,AlignLeft,AlignLeft] [0.0,0.0,0.0]
|
||||
[[]
|
||||
,[]
|
||||
,[]]
|
||||
[[[Para [Str "1"]]
|
||||
,[Para [Str "2"]]
|
||||
,[Para [Str "3"]]]
|
||||
,[[Para [Str "4"]]
|
||||
,[Para [Str "5"]]
|
||||
,[Para [Str "6"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "6"]]]]
|
||||
[]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "6"]]]]
|
||||
[]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "6"]]]]
|
||||
[]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignLeft,Nothing),(AlignLeft,Nothing),(AlignLeft,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "3"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "4"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "5"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "6"]]]]
|
||||
[]
|
||||
,Header 2 ("empty-tables",[],[]) [Str "Empty",Space,Str "Tables"]
|
||||
,Para [Str "This",Space,Str "section",Space,Str "should",Space,Str "be",Space,Str "empty."]]
|
||||
|
|
|
@ -275,18 +275,37 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
,[Para [Str "$22,000",Space,Str "is",Space,Str "a",Space,Emph [Str "lot"],Space,Str "of",Space,Str "money.",Space,Str "So",Space,Str "is",Space,Str "$34,000.",Space,Str "(It",Space,Str "worked",Space,Str "if",SoftBreak,Quoted DoubleQuote [Str "lot"],Space,Str "is",Space,Str "emphasized.)"]]
|
||||
,[Para [Str "Escaped",Space,Code ("",[],[]) "$",Str ":",Space,Str "$73",Space,Emph [Str "this",Space,Str "should",Space,Str "be",Space,Str "emphasized"],Space,Str "23$."]]]
|
||||
,Para [Str "Here\8217s",Space,Str "a",Space,Str "LaTeX",Space,Str "table:"]
|
||||
,Table [] [AlignLeft,AlignLeft] [0.0,0.0]
|
||||
[[Plain [Str "Animal"]]
|
||||
,[Plain [Str "Number"]]]
|
||||
[[[Plain [Str "Dog"]]
|
||||
,[Plain [Str "2"]]]
|
||||
,[[Plain [Str "Cat"]]
|
||||
,[Plain [Str "1"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignLeft,Nothing),(AlignLeft,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Animal"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Number"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Dog"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "2"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Cat"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]]]
|
||||
[]
|
||||
,Para [Str "A",Space,Str "table",Space,Str "with",Space,Str "one",Space,Str "column:"]
|
||||
,Table [] [AlignCenter] [0.0]
|
||||
[[]]
|
||||
[[[Plain [Str "Animal"]]]
|
||||
,[[Plain [Str "Vegetable"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignCenter,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Animal"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Vegetable"]]]]
|
||||
[]
|
||||
,HorizontalRule
|
||||
,Header 1 ("special-characters",[],[]) [Str "Special",Space,Str "Characters"]
|
||||
,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "unicode:"]
|
||||
|
|
|
@ -105,76 +105,170 @@ Pandoc (Meta {unMeta = fromList [("date",MetaInlines [Str "Oct",Space,Str "17,",
|
|||
,Header 1 ("",[],[]) [Str "Macros"]
|
||||
,Para [Strong [Str "Me",Space,Str "Myself"],Space,Str "and",Space,Str "I.",Space,Emph [Str "The",Space,Str "author",Space,Str "is",Space,Str "John",Space,Str "Jones."],Space,Str "It's",Space,Str "The",Space,Strong [Str "Author"],Str "."]
|
||||
,Header 1 ("",[],[]) [Str "Tables"]
|
||||
,Table [] [AlignRight,AlignLeft,AlignCenter,AlignLeft] [0.0,0.0,0.0,0.0]
|
||||
[[Plain [Str "Right"]]
|
||||
,[Plain [Str "Left"]]
|
||||
,[Plain [Str "Center"]]
|
||||
,[Plain [Str "Default"]]]
|
||||
[[[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]]
|
||||
,[[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]]
|
||||
,[[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]]]
|
||||
,Table [] [AlignRight,AlignLeft,AlignCenter,AlignLeft] [0.0,0.0,0.0,0.0]
|
||||
[[Plain [Str "Right"]]
|
||||
,[Plain [Str "Left"]]
|
||||
,[Plain [Str "Center"]]
|
||||
,[Plain [Str "Left",Space,Emph [Str "more"]]]]
|
||||
[[[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]]
|
||||
,[[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]]
|
||||
,[[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]]]
|
||||
,Table [] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.0,0.0,0.0,0.0]
|
||||
[[Plain [Str "Centered",Space,Str "Header"]]
|
||||
,[Plain [Str "Left",Space,Str "Aligned"]]
|
||||
,[Plain [Str "Right",Space,Str "Aligned"]]
|
||||
,[Plain [Str "Default",Space,Str "aligned"]]]
|
||||
[[[Plain [Str "First"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "12.0"]]
|
||||
,[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines."]]]
|
||||
,[[Plain [Str "Second"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "5.0"]]
|
||||
,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignLeft,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Right"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Left"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Center"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Default"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]]]
|
||||
[]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignLeft,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Right"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Left"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Center"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Left",Space,Emph [Str "more"]]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]]]
|
||||
[]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignCenter,Nothing),(AlignLeft,Nothing),(AlignRight,Nothing),(AlignLeft,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Centered",Space,Str "Header"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Left",Space,Str "Aligned"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Right",Space,Str "Aligned"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Default",Space,Str "aligned"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "First"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "row"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12.0"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines."]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Second"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "row"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "5.0"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]]
|
||||
[]
|
||||
,Para [Str "Table",Space,Str "without",Space,Str "column",Space,Str "headers:"]
|
||||
,Table [] [AlignRight,AlignLeft,AlignCenter,AlignRight] [0.0,0.0,0.0,0.0]
|
||||
[[]
|
||||
,[]
|
||||
,[]
|
||||
,[]]
|
||||
[[[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]
|
||||
,[Plain [Str "12"]]]
|
||||
,[[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]
|
||||
,[Plain [Str "123"]]]
|
||||
,[[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]]]
|
||||
,Table [] [AlignRight,AlignLeft] [0.5,0.5]
|
||||
[[]
|
||||
,[]]
|
||||
[[[Plain [Str "a"]]
|
||||
,[Plain [Str "b"]]]
|
||||
,[[Para [Str "one"]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignRight,Nothing),(AlignLeft,Nothing),(AlignCenter,Nothing),(AlignRight,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "12"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "123"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "1"]]]]
|
||||
[]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignRight,Just 0.5),(AlignLeft,Just 0.5)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "a"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "b"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "one"]
|
||||
,Para [Str "two"]]
|
||||
,[CodeBlock ("",[],[]) "some\n code"]]]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[CodeBlock ("",[],[]) "some\n code"]]]
|
||||
[]]
|
||||
|
|
|
@ -96,84 +96,176 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "Author",S
|
|||
,[Str "Continuation",Space,Str "line"]
|
||||
,[Str "\160\160and",Space,Str "another"]]
|
||||
,Header 2 ("grid-tables",[],[]) [Str "Grid",Space,Str "Tables"]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.2638888888888889,0.16666666666666666,0.18055555555555555]
|
||||
[[Plain [Str "col",Space,Str "1"]]
|
||||
,[Plain [Str "col",Space,Str "2"]]
|
||||
,[Plain [Str "col",Space,Str "3"]]]
|
||||
[[[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]]
|
||||
,[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]]
|
||||
,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]]
|
||||
,[[Plain [Str "r2",Space,Str "d"]]
|
||||
,[Plain [Str "e"]]
|
||||
,[Plain [Str "f"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Just 0.2638888888888889),(AlignDefault,Just 0.16666666666666666),(AlignDefault,Just 0.18055555555555555)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "col",Space,Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "col",Space,Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "col",Space,Str "3"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "r2",Space,Str "d"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "e"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "f"]]]]
|
||||
[]
|
||||
,Para [Str "Headless"]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.2638888888888889,0.16666666666666666,0.18055555555555555]
|
||||
[[]
|
||||
,[]
|
||||
,[]]
|
||||
[[[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]]
|
||||
,[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]]
|
||||
,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]]
|
||||
,[[Plain [Str "r2",Space,Str "d"]]
|
||||
,[Plain [Str "e"]]
|
||||
,[Plain [Str "f"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Just 0.2638888888888889),(AlignDefault,Just 0.16666666666666666),(AlignDefault,Just 0.18055555555555555)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "r2",Space,Str "d"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "e"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "f"]]]]
|
||||
[]
|
||||
,Para [Str "With",Space,Str "alignments"]
|
||||
,Table [] [AlignRight,AlignLeft,AlignCenter] [0.2638888888888889,0.16666666666666666,0.18055555555555555]
|
||||
[[Plain [Str "col",Space,Str "1"]]
|
||||
,[Plain [Str "col",Space,Str "2"]]
|
||||
,[Plain [Str "col",Space,Str "3"]]]
|
||||
[[[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]]
|
||||
,[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]]
|
||||
,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]]
|
||||
,[[Plain [Str "r2",Space,Str "d"]]
|
||||
,[Plain [Str "e"]]
|
||||
,[Plain [Str "f"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignRight,Just 0.2638888888888889),(AlignLeft,Just 0.16666666666666666),(AlignCenter,Just 0.18055555555555555)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "col",Space,Str "1"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "col",Space,Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "col",Space,Str "3"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "r2",Space,Str "d"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "e"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "f"]]]]
|
||||
[]
|
||||
,Para [Str "Headless",Space,Str "with",Space,Str "alignments"]
|
||||
,Table [] [AlignRight,AlignLeft,AlignCenter] [0.2638888888888889,0.16666666666666666,0.18055555555555555]
|
||||
[[]
|
||||
,[]
|
||||
,[]]
|
||||
[[[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]]
|
||||
,[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]]
|
||||
,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]]
|
||||
,[[Plain [Str "r2",Space,Str "d"]]
|
||||
,[Plain [Str "e"]]
|
||||
,[Plain [Str "f"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignRight,Just 0.2638888888888889),(AlignLeft,Just 0.16666666666666666),(AlignCenter,Just 0.18055555555555555)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "r2",Space,Str "d"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "e"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "f"]]]]
|
||||
[]
|
||||
,Para [Str "Spaces",Space,Str "at",Space,Str "ends",Space,Str "of",Space,Str "lines"]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.2638888888888889,0.16666666666666666,0.18055555555555555]
|
||||
[[]
|
||||
,[]
|
||||
,[]]
|
||||
[[[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]]
|
||||
,[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]]
|
||||
,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]]
|
||||
,[[Plain [Str "r2",Space,Str "d"]]
|
||||
,[Plain [Str "e"]]
|
||||
,[Plain [Str "f"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Just 0.2638888888888889),(AlignDefault,Just 0.16666666666666666),(AlignDefault,Just 0.18055555555555555)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "r2",Space,Str "d"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "e"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "f"]]]]
|
||||
[]
|
||||
,Para [Str "Multiple",Space,Str "blocks",Space,Str "in",Space,Str "a",Space,Str "cell"]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.2638888888888889,0.16666666666666666,0.18055555555555555]
|
||||
[[]
|
||||
,[]
|
||||
,[]]
|
||||
[[[Header 1 ("col-1",[],[]) [Str "col",Space,Str "1"]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Just 0.2638888888888889),(AlignDefault,Just 0.16666666666666666),(AlignDefault,Just 0.18055555555555555)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Header 1 ("col-1",[],[]) [Str "col",Space,Str "1"]
|
||||
,Plain [Str "col",Space,Str "1"]]
|
||||
,[Header 1 ("col-2",[],[]) [Str "col",Space,Str "2"]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Header 1 ("col-2",[],[]) [Str "col",Space,Str "2"]
|
||||
,Plain [Str "col",Space,Str "2"]]
|
||||
,[Header 1 ("col-3",[],[]) [Str "col",Space,Str "3"]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Header 1 ("col-3",[],[]) [Str "col",Space,Str "3"]
|
||||
,Plain [Str "col",Space,Str "3"]]]
|
||||
,[[Para [Str "r1",Space,Str "a"]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "r1",Space,Str "a"]
|
||||
,Para [Str "r1",Space,Str "bis"]]
|
||||
,[BulletList
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[BulletList
|
||||
[[Plain [Str "b"]]
|
||||
,[Plain [Str "b",Space,Str "2"]]
|
||||
,[Plain [Str "b",Space,Str "2"]]]]
|
||||
,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2",SoftBreak,Str "c",Space,Str "2"]]]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Plain [Str "c",SoftBreak,Str "c",Space,Str "2",SoftBreak,Str "c",Space,Str "2"]]]]
|
||||
[]
|
||||
,Para [Str "Empty",Space,Str "cells"]
|
||||
,Table [] [AlignDefault,AlignDefault] [5.555555555555555e-2,5.555555555555555e-2]
|
||||
[[]
|
||||
,[]]
|
||||
[[[]
|
||||
,[]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Just 5.555555555555555e-2),(AlignDefault,Just 5.555555555555555e-2)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[]
|
||||
,Header 2 ("entities-in-links-and-titles",[],[]) [Str "Entities",Space,Str "in",Space,Str "links",Space,Str "and",Space,Str "titles"]
|
||||
,Para [Link ("",[],[]) [Str "link"] ("/\252rl","\246\246!")]
|
||||
,Para [Link ("",["uri"],[]) [Str "http://g\246\246gle.com"] ("http://g\246\246gle.com","")]
|
||||
|
|
|
@ -187,76 +187,177 @@ Pandoc (Meta {unMeta = fromList []})
|
|||
,RawBlock (Format "mediawiki") "{{Thankyou|all your effort|Me}}"
|
||||
,Para [Str "Written",Space,RawInline (Format "mediawiki") "{{{date}}}",Space,Str "by",Space,RawInline (Format "mediawiki") "{{{name}}}",Str "."]
|
||||
,Header 2 ("tables",[],[]) [Str "tables"]
|
||||
,Table [] [AlignDefault,AlignDefault] [0.0,0.0]
|
||||
[[]
|
||||
,[]]
|
||||
[[[Para [Str "Orange"]]
|
||||
,[Para [Str "Apple"]]]
|
||||
,[[Para [Str "Bread"]]
|
||||
,[Para [Str "Pie"]]]
|
||||
,[[Para [Str "Butter"]]
|
||||
,[Para [Str "Ice",Space,Str "cream"]]]]
|
||||
,Table [Str "Food",Space,Str "complements"] [AlignDefault,AlignDefault] [0.0,0.0]
|
||||
[[Para [Str "Orange"]]
|
||||
,[Para [Str "Apple"]]]
|
||||
[[[Para [Str "Bread"]]
|
||||
,[Para [Str "Pie"]]]
|
||||
,[[Para [Str "Butter"]]
|
||||
,[Para [Str "Ice",Space,Str "cream"]]]]
|
||||
,Table [Str "Food",Space,Str "complements"] [AlignDefault,AlignDefault] [0.0,0.0]
|
||||
[[Para [Str "Orange"]]
|
||||
,[Para [Str "Apple"]]]
|
||||
[[[Para [Str "Bread"]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Orange"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Apple"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Bread"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Pie"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Butter"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Ice",Space,Str "cream"]]]]
|
||||
[]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[Para [Str "Food",Space,Str "complements"]]) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Orange"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Apple"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Bread"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Pie"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Butter"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Ice",Space,Str "cream"]]]]
|
||||
[]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[Para [Str "Food",Space,Str "complements"]]) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Orange"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Apple"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Bread"]
|
||||
,Para [Str "and",Space,Str "cheese"]]
|
||||
,[Para [Str "Pie"]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Pie"]
|
||||
,OrderedList (1,DefaultStyle,DefaultDelim)
|
||||
[[Plain [Str "apple"]]
|
||||
,[Plain [Str "carrot"]]]]]]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[[]
|
||||
,[]
|
||||
,[]]
|
||||
[[[Para [Str "Orange"]]
|
||||
,[Para [Str "Apple"]]
|
||||
,[Para [Str "more"]]]
|
||||
,[[Para [Str "Bread"]]
|
||||
,[Para [Str "Pie"]]
|
||||
,[Para [Str "more"]]]
|
||||
,[[Para [Str "Butter"]]
|
||||
,[Para [Str "Ice",Space,Str "cream"]]
|
||||
,[Para [Str "and",Space,Str "more"]]]]
|
||||
,Table [] [AlignLeft,AlignRight,AlignCenter] [0.25,0.125,0.125]
|
||||
[[Para [Str "Left"]]
|
||||
,[Para [Str "Right"]]
|
||||
,[Para [Str "Center"]]]
|
||||
[[[Para [Str "left"]]
|
||||
,[Para [Str "15.00"]]
|
||||
,[Para [Str "centered"]]]
|
||||
,[[Para [Str "more"]]
|
||||
,[Para [Str "2.0"]]
|
||||
,[Para [Str "more"]]]]
|
||||
,Table [] [AlignDefault,AlignDefault] [0.0,0.0]
|
||||
[[]
|
||||
,[]]
|
||||
[[[Para [Str "Orange"]]
|
||||
,[Para [Str "Apple"]]]
|
||||
,[[Para [Str "Bread"]]
|
||||
,[Table [] [AlignDefault,AlignDefault] [0.0,0.0]
|
||||
[[Para [Str "fruit"]]
|
||||
,[Para [Str "topping"]]]
|
||||
[[[Para [Str "apple"]]
|
||||
,[Para [Str "ice",Space,Str "cream"]]]]]]
|
||||
,[[Para [Str "Butter"]]
|
||||
,[Para [Str "Ice",Space,Str "cream"]]]]
|
||||
,Table [] [AlignDefault] [0.0]
|
||||
[[]]
|
||||
[[[Para [Str "Orange"]]]]
|
||||
[]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Orange"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Apple"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "more"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Bread"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Pie"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "more"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Butter"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Ice",Space,Str "cream"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "and",Space,Str "more"]]]]
|
||||
[]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignLeft,Just 0.25),(AlignRight,Just 0.125),(AlignCenter,Just 0.125)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Left"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Right"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Center"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "left"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "15.00"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "centered"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "more"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "2.0"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "more"]]]]
|
||||
[]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Orange"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Apple"]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Bread"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "fruit"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "topping"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "apple"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "ice",Space,Str "cream"]]]]
|
||||
[]]]
|
||||
,Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Butter"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Ice",Space,Str "cream"]]]]
|
||||
[]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "Orange"]]]]
|
||||
[]
|
||||
,Para [Str "Paragraph",Space,Str "after",Space,Str "the",Space,Str "table."]
|
||||
,Table [] [AlignDefault,AlignDefault] [0.0,0.0]
|
||||
[[Para [Str "fruit"]]
|
||||
,[Para [Str "topping"]]]
|
||||
[[[Para [Str "apple"]]
|
||||
,[Para [Str "ice",Space,Str "cream"]]]]
|
||||
,Table ("",[],[]) (Caption Nothing
|
||||
[]) [(AlignDefault,Nothing),(AlignDefault,Nothing)] 0
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "fruit"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "topping"]]]]
|
||||
[Row ("",[],[])
|
||||
[Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "apple"]]
|
||||
,Cell ("",[],[]) Nothing 1 1
|
||||
[Para [Str "ice",Space,Str "cream"]]]]
|
||||
[]
|
||||
,Header 2 ("notes",[],[]) [Str "notes"]
|
||||
,Para [Str "My",Space,Str "note!",Note [Plain [Str "This."]]]
|
||||
,Para [Str "URL",Space,Str "note.",Note [Plain [Link ("",[],[]) [Str "http://docs.python.org/library/functions.html#range"] ("http://docs.python.org/library/functions.html#range","")]]]]
|
||||
|
|
Some files were not shown because too many files have changed in this diff Show more
Loading…
Add table
Reference in a new issue