diff --git a/MANUAL.txt b/MANUAL.txt index f0d3c8965a7c..078c38c96c6a 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -3173,6 +3173,17 @@ In the `context` output format this enables the use of [Natural Tables Natural tables allow more fine-grained global customization but come at a performance penalty compared to extreme tables. +#### Extension: `native_figures` #### + +Use pandoc's native `Figure` element for content inside `
` tags, in the +case of HTML, or `figure` environments, in case of LaTeX. This, in turn, allows +some writers to produce more accurate representations of figures. It also +allows the use of the `Figure` element in filters, for custom figure output. + +This extension can be enabled/disabled for the following formats: + +input formats +: `latex` `html` # Pandoc's Markdown diff --git a/cabal.project b/cabal.project index 7256c16ec638..0a54b08c6c0a 100644 --- a/cabal.project +++ b/cabal.project @@ -4,6 +4,7 @@ flags: +embed_data_files source-repository-package type: git + location: https://github.com/argent0/pandoc-types + tag: 5b32019746d1692c593c080f9a8ee45c7d25ecba location: https://github.com/jgm/citeproc.git tag: b27201c3ac48ffd2853f77152df19b6e2cf36987 - diff --git a/data/pandoc.lua b/data/pandoc.lua index 35ca20a84a04..fb0d91fc43c9 100644 --- a/data/pandoc.lua +++ b/data/pandoc.lua @@ -469,6 +469,22 @@ M.Div = M.Block:create_constructor( {{attr = {"identifier", "classes", "attributes"}}, "content"} ) + +--- Creates a figure element. +-- @function Figure +-- @tparam {Block,...} content figure block contents +-- @tparam Caption caption figure caption +-- @tparam[opt] Attr attr element attributes +-- @treturn Block figure element +M.Figure = M.Block:create_constructor( + "Figure", + function(content, caption, attr) + return {c = {ensureAttr(attr), caption, ensureList(content)}} + end, + {{attr = {"identifier", "classes", "attributes"}}, "caption", "content"} +) + + --- Creates a header element. -- @function Header -- @tparam int level header level diff --git a/pandoc.cabal b/pandoc.cabal index 3de7da39cb43..5837de6c5fe1 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -206,6 +206,7 @@ extra-source-files: test/bodybg.gif test/*.native test/command/*.md + test/command/figures/*.md test/command/*.csl test/command/biblio.bib test/command/averroes.bib diff --git a/src/Text/Pandoc/Extensions.hs b/src/Text/Pandoc/Extensions.hs index f11e677235db..51b822e388c6 100644 --- a/src/Text/Pandoc/Extensions.hs +++ b/src/Text/Pandoc/Extensions.hs @@ -126,6 +126,7 @@ data Extension = | Ext_mmd_title_block -- ^ Multimarkdown metadata block | Ext_multiline_tables -- ^ Pandoc-style multiline tables | Ext_native_divs -- ^ Use Div blocks for contents of
tags + | Ext_native_figures -- ^ Use Figure blocks for contenst of
tags. | Ext_native_spans -- ^ Use Span inlines for contents of | Ext_native_numbering -- ^ Use output format's native numbering for figures and tables | Ext_ntb -- ^ ConTeXt Natural Tables @@ -527,6 +528,7 @@ getAllExtensions f = universalExtensions <> getAll f getAll "html" = autoIdExtensions <> extensionsFromList [ Ext_native_divs + , Ext_native_figures , Ext_line_blocks , Ext_native_spans , Ext_empty_paragraphs @@ -552,6 +554,7 @@ getAllExtensions f = universalExtensions <> getAll f , Ext_raw_tex , Ext_task_lists , Ext_literate_haskell + , Ext_native_figures ] getAll "beamer" = getAll "latex" getAll "context" = autoIdExtensions <> diff --git a/src/Text/Pandoc/Lua/Marshaling/AST.hs b/src/Text/Pandoc/Lua/Marshaling/AST.hs index 8e12d232cabc..ce8183a22d26 100644 --- a/src/Text/Pandoc/Lua/Marshaling/AST.hs +++ b/src/Text/Pandoc/Lua/Marshaling/AST.hs @@ -160,6 +160,7 @@ pushBlock = \case CodeBlock attr code -> pushViaConstructor "CodeBlock" code (LuaAttr attr) DefinitionList items -> pushViaConstructor "DefinitionList" items Div attr blcks -> pushViaConstructor "Div" blcks (LuaAttr attr) + Figure attr capt blcks -> pushViaConstructor "Figure" blcks capt (LuaAttr attr) Header lvl attr inlns -> pushViaConstructor "Header" lvl inlns (LuaAttr attr) HorizontalRule -> pushViaConstructor "HorizontalRule" LineBlock blcks -> pushViaConstructor "LineBlock" blcks @@ -182,6 +183,8 @@ peekBlock idx = defineHowTo "get Block value" $! do "CodeBlock" -> withAttr CodeBlock <$!> elementContent "DefinitionList" -> DefinitionList <$!> elementContent "Div" -> withAttr Div <$!> elementContent + "Figure" -> (\(LuaAttr attr, capt, bs) -> Figure attr capt bs) + <$!> elementContent "Header" -> (\(lvl, LuaAttr attr, lst) -> Header lvl attr lst) <$!> elementContent "HorizontalRule" -> return HorizontalRule diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index fdf4f28e0bff..2ebbeacc4058 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -35,6 +35,7 @@ import Data.List.Split (splitWhen) import Data.List (foldl') import qualified Data.Map as M import Data.Maybe (fromMaybe, isJust, isNothing) +import Data.Either (partitionEithers) import Data.Monoid (First (..)) import qualified Data.Set as Set import Data.Text (Text) @@ -57,7 +58,8 @@ import Text.Pandoc.Error import Text.Pandoc.Logging import Text.Pandoc.Options ( Extension (Ext_epub_html_exts, Ext_empty_paragraphs, Ext_native_divs, - Ext_native_spans, Ext_raw_html, Ext_line_blocks, Ext_raw_tex), + Ext_native_spans, Ext_raw_html, Ext_line_blocks, Ext_raw_tex, + Ext_native_figures), ReaderOptions (readerExtensions, readerStripComments), extensionEnabled) import Text.Pandoc.Parsing hiding ((<|>)) @@ -535,24 +537,43 @@ pPara = do <|> return (B.para contents) pFigure :: PandocMonad m => TagParser m Blocks -pFigure = try $ do - TagOpen _ _ <- pSatisfy (matchTagOpen "figure" []) - skipMany pBlank - let pImg = (\x -> (Just x, Nothing)) <$> - (pInTag TagsOmittable "p" pImage <* skipMany pBlank) - pCapt = (\x -> (Nothing, Just x)) <$> do - bs <- pInTags "figcaption" block - return $ blocksToInlines' $ B.toList bs - pSkip = (Nothing, Nothing) <$ pSatisfy (not . matchTagClose "figure") - res <- many (pImg <|> pCapt <|> pSkip) - let mbimg = msum $ map fst res - let mbcap = msum $ map snd res - TagClose _ <- pSatisfy (matchTagClose "figure") - let caption = fromMaybe mempty mbcap - case B.toList <$> mbimg of - Just [Image attr _ (url, tit)] -> - return $ B.para $ B.imageWith attr url ("fig:" <> tit) caption - _ -> mzero +pFigure = do + has_native_figures <- + extensionEnabled Ext_native_figures <$> getOption readerExtensions + if has_native_figures + then pNativeFigure + else try $ do + TagOpen _ _ <- pSatisfy (matchTagOpen "figure" []) + skipMany pBlank + let pImg = (\x -> (Just x, Nothing)) <$> + (pInTag TagsOmittable "p" pImage <* skipMany pBlank) + pCapt = (\x -> (Nothing, Just x)) <$> do + bs <- pInTags "figcaption" block + return $ blocksToInlines' $ B.toList bs + pSkip = (Nothing, Nothing) <$ pSatisfy (not . matchTagClose "figure") + -- res :: [(Maybe Inlines, Maybe Inlines)] + -- [(Just img, Nothing), (Nothing, Just caption), ...] + res <- many (pImg <|> pCapt <|> pSkip) + -- Takes the first image and the first caption, if any, drop the rest. + let mbimg = msum $ map fst res + let mbcap = msum $ map snd res -- mbcap :: Maybe Inlines + TagClose _ <- pSatisfy (matchTagClose "figure") + let caption = fromMaybe mempty mbcap + -- only process one image + case B.toList <$> mbimg of + Just [Image attr _ (url, tit)] -> + return $ B.simpleFigureWith attr caption url tit + _ -> mzero + +pNativeFigure :: PandocMonad m => TagParser m Blocks +pNativeFigure = try $ do + TagOpen tag attrList <- lookAhead $ pSatisfy (matchTagOpen "figure" []) + --let (ident, classes, kvs) = toAttr attr + contents <- pInTags tag (many $ Left <$> pInTags "figcaption" block <|> (Right <$> block)) + + let (captions, rest) = partitionEithers contents + -- I should capture the caption + return $ B.figureWith (toAttr attrList) (Caption Nothing (B.toList (mconcat captions))) $ mconcat rest pCodeBlock :: PandocMonad m => TagParser m Blocks pCodeBlock = try $ do diff --git a/src/Text/Pandoc/Readers/JATS.hs b/src/Text/Pandoc/Readers/JATS.hs index 9cdbf1611186..37e0d13bca3e 100644 --- a/src/Text/Pandoc/Readers/JATS.hs +++ b/src/Text/Pandoc/Readers/JATS.hs @@ -35,6 +35,7 @@ import Text.Pandoc.XML.Light import qualified Data.Set as S (fromList, member) import Data.Set ((\\)) import Text.Pandoc.Sources (ToSources(..), sourcesToText) +import qualified Data.Foldable as DF type JATS m = StateT JATSState m @@ -226,9 +227,19 @@ parseBlock (Elem e) = mapM getInlines (filterChildren (const True) t) Nothing -> return mempty - img <- getGraphic (Just (capt, attrValue "id" e)) g - return $ para img + + let figAttributes = DF.toList $ + ("alt", ) . strContent <$> + filterChild (named "alt-text") e + + return $ simpleFigureWith + (attrValue "id" e, [], figAttributes) + capt + (attrValue "href" g) + (attrValue "title" g) + _ -> divWith (attrValue "id" e, ["fig"], []) <$> getBlocks e + parseTable = do let isCaption x = named "title" x || named "caption" x capt <- case filterChild isCaption e of diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index 5d3ff5f9553f..a625232db2e8 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -32,6 +32,7 @@ import Data.Maybe (fromMaybe, maybeToList) import qualified Data.Set as Set import Data.Text (Text) import qualified Data.Text as T +import Data.Either (partitionEithers) import Skylighting (defaultSyntaxMap) import System.FilePath (addExtension, replaceExtension, takeExtension) import Text.Collate.Lang (renderLang) @@ -935,8 +936,8 @@ environments = M.union (tableEnvironments blocks inline) $ , ("letter", env "letter" letterContents) , ("minipage", env "minipage" $ skipopts *> spaces *> optional braced *> spaces *> blocks) - , ("figure", env "figure" $ skipopts *> figure) - , ("subfigure", env "subfigure" $ skipopts *> tok *> figure) + , ("figure", env "figure" $ skipopts *> Text.Pandoc.Readers.LaTeX.figure) + , ("subfigure", env "subfigure" $ skipopts *> tok *> Text.Pandoc.Readers.LaTeX.figure) , ("center", divWith ("", ["center"], []) <$> env "center" blocks) , ("quote", blockQuote <$> env "quote" blocks) , ("quotation", blockQuote <$> env "quotation" blocks) @@ -1088,30 +1089,55 @@ letterContents = do return $ addr <> bs -- sig added by \closing figure :: PandocMonad m => LP m Blocks -figure = try $ do +figure = do + has_native_figures <- + extensionEnabled Ext_native_figures <$> getOption readerExtensions + if has_native_figures + then nativeFigure + else try $ do + resetCaption + blocks >>= addImageCaption + +nativeFigure :: PandocMonad m => LP m Blocks +nativeFigure = try $ do resetCaption - blocks >>= addImageCaption + innerContent <- many $ try (Left <$> label) <|> (Right <$> block) + let content = walk go $ mconcat $ snd $ partitionEithers innerContent + labelResult <- sLastLabel <$> getState + let attr = case labelResult of + Just lab -> (lab, [], []) + _ -> nullAttr + captResult <- sCaption <$> getState + case captResult of + Nothing -> return $ B.figureWith attr (Caption Nothing []) content + Just capt -> return $ B.figureWith attr (B.caption Nothing $ B.plain capt) content + + where + -- Remove the `Image` caption b.c. it's on the `Figure` + go (Para [Image attr _ target]) = Plain [Image attr [] target] + go x = x addImageCaption :: PandocMonad m => Blocks -> LP m Blocks addImageCaption = walkM go - where go (Image attr@(_, cls, kvs) alt (src,tit)) + where go p@(Para [Image attr@(_, cls, kvs) _ (src, tit)]) | not ("fig:" `T.isPrefixOf` tit) = do st <- getState - let (alt', tit') = case sCaption st of - Just ils -> (toList ils, "fig:" <> tit) - Nothing -> (alt, tit) - attr' = case sLastLabel st of - Just lab -> (lab, cls, kvs) - Nothing -> attr - case attr' of - ("", _, _) -> return () - (ident, _, _) -> do - num <- getNextNumber sLastFigureNum - setState - st{ sLastFigureNum = num - , sLabels = M.insert ident - [Str (renderDottedNum num)] (sLabels st) } - return $ Image attr' alt' (src, tit') + case sCaption st of + Nothing -> return p + Just figureCaption -> do + let attr' = case sLastLabel st of + Just lab -> (lab, cls, kvs) + Nothing -> attr + case attr' of + ("", _, _) -> return () + (ident, _, _) -> do + num <- getNextNumber sLastFigureNum + setState + st{ sLastFigureNum = num + , sLabels = M.insert ident + [Str (renderDottedNum num)] (sLabels st) } + + return $ SimpleFigure attr' (B.toList figureCaption) (src, tit) go x = return x coloredBlock :: PandocMonad m => Text -> LP m Blocks diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 45594e0fafc0..ac30d6f548d6 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -1013,19 +1013,18 @@ normalDefinitionList = do para :: PandocMonad m => MarkdownParser m (F Blocks) para = try $ do exts <- getOption readerExtensions - let implicitFigures x - | extensionEnabled Ext_implicit_figures exts = do - x' <- x - case B.toList x' of - [Image attr alt (src,tit)] - | not (null alt) -> - -- the fig: at beginning of title indicates a figure - return $ B.singleton - $ Image attr alt (src, "fig:" <> tit) - _ -> return x' - | otherwise = x - result <- implicitFigures . trimInlinesF <$> inlines1 - option (B.plain <$> result) + + result <- trimInlinesF <$> inlines1 + let figureOr constr inlns = + case B.toList inlns of + [Image attr figCaption (src, tit)] + | extensionEnabled Ext_implicit_figures exts + , not (null figCaption) -> do + B.simpleFigureWith attr (B.fromList figCaption) src tit + + _ -> constr inlns + + option (figureOr B.plain <$> result) $ try $ do newline (mempty <$ blanklines) @@ -1047,7 +1046,7 @@ para = try $ do if divLevel > 0 then lookAhead divFenceEnd else mzero - return $ B.para <$> result + return $ figureOr B.para <$> result plain :: PandocMonad m => MarkdownParser m (F Blocks) plain = fmap B.plain . trimInlinesF <$> inlines1 diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs index 825e4a2eb388..9348a8053317 100644 --- a/src/Text/Pandoc/Readers/MediaWiki.hs +++ b/src/Text/Pandoc/Readers/MediaWiki.hs @@ -201,7 +201,12 @@ para = do contents <- trimInlines . mconcat <$> many1 inline if F.all (==Space) contents then return mempty - else return $ B.para contents + else case B.toList contents of + -- For the MediaWiki format all images are considered figures + [Image attr figureCaption (src, title)] -> + return $ B.simpleFigureWith + attr (B.fromList figureCaption) src title + _ -> return $ B.para contents table :: PandocMonad m => MWParser m Blocks table = do @@ -631,7 +636,7 @@ image = try $ do let attr = ("", [], kvs) caption <- (B.str fname <$ sym "]]") <|> try (char '|' *> (mconcat <$> manyTill inline (sym "]]"))) - return $ B.imageWith attr fname ("fig:" <> stringify caption) caption + return $ B.imageWith attr fname (stringify caption) caption imageOption :: PandocMonad m => MWParser m Text imageOption = try $ char '|' *> opt diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs index 2ec97d903edb..9a689b0e8750 100644 --- a/src/Text/Pandoc/Readers/Org/Blocks.hs +++ b/src/Text/Pandoc/Readers/Org/Blocks.hs @@ -474,15 +474,16 @@ figure = try $ do figCaption = fromMaybe mempty $ blockAttrCaption figAttrs figKeyVals = blockAttrKeyValues figAttrs attr = (figLabel, mempty, figKeyVals) - figTitle = (if isFigure then withFigPrefix else id) figName - in - B.para . B.imageWith attr imgSrc figTitle <$> figCaption - - withFigPrefix :: Text -> Text - withFigPrefix cs = - if "fig:" `T.isPrefixOf` cs - then cs - else "fig:" <> cs + in if isFigure + then (\c -> + B.simpleFigureWith + attr c imgSrc (unstackFig figName)) <$> figCaption + else B.para . B.imageWith attr imgSrc figName <$> figCaption + unstackFig :: Text -> Text + unstackFig figName = + if "fig:" `T.isPrefixOf` figName + then T.drop 4 figName + else figName -- | Succeeds if looking at the end of the current paragraph endOfParagraph :: Monad m => OrgParser m () diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index ff891d3c60d9..950f03dccdb6 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -725,8 +725,8 @@ directive' = do "figure" -> do (caption, legend) <- parseFromString' extractCaption body' let src = escapeURI $ trim top - return $ B.para (B.imageWith (imgAttr "figclass") src "fig:" - caption) <> legend + return $ B.simpleFigureWith + (imgAttr "figclass") caption src "" <> legend "image" -> do let src = escapeURI $ trim top let alt = B.str $ maybe "image" trim $ lookup "alt" fields diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 920edca7b3a6..602ddc5b8504 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -949,6 +949,7 @@ blockToInlines (Table _ _ _ (TableHead _ hbd) bodies (TableFoot _ fbd)) = unTableBodies = concatMap unTableBody blockToInlines (Div _ blks) = blocksToInlines' blks blockToInlines Null = mempty +blockToInlines (Figure _ _ body) = blocksToInlines' body blocksToInlinesWithSep :: Inlines -> [Block] -> Inlines blocksToInlinesWithSep sep = diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs index bcef4a0898c3..1223430d3846 100644 --- a/src/Text/Pandoc/Writers/AsciiDoc.hs +++ b/src/Text/Pandoc/Writers/AsciiDoc.hs @@ -149,9 +149,8 @@ blockToAsciiDoc opts (Div (id',"section":_,_) blockToAsciiDoc opts (Plain inlines) = do contents <- inlineListToAsciiDoc opts inlines return $ contents <> blankline -blockToAsciiDoc opts (Para [Image attr alternate (src,tgt)]) +blockToAsciiDoc opts (SimpleFigure attr alternate (src, tit)) -- image::images/logo.png[Company logo, title="blah"] - | Just tit <- T.stripPrefix "fig:" tgt = (\args -> "image::" <> args <> blankline) <$> imageArguments opts attr alternate src tit blockToAsciiDoc opts (Para inlines) = do @@ -187,7 +186,7 @@ blockToAsciiDoc opts (Header level (ident,_,_) inlines) = do return $ identifier $$ nowrap (text (replicate (level + 1) '=') <> space <> contents) <> blankline - +blockToAsciiDoc opts (Figure attr _ body) = blockToAsciiDoc opts $ Div attr body blockToAsciiDoc _ (CodeBlock (_,classes,_) str) = return $ flush ( if null classes then "...." $$ literal str $$ "...." diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index 3cafcefba909..5361dd7d59b1 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -162,10 +162,7 @@ blockToConTeXt (Div attr@(_,"section":_,_) innerContents <- blockListToConTeXt xs return $ header' $$ innerContents $$ footer' blockToConTeXt (Plain lst) = inlineListToConTeXt lst --- title beginning with fig: indicates that the image is a figure -blockToConTeXt (Para [Image attr txt (src,tgt)]) - | Just _ <- T.stripPrefix "fig:" tgt - = do +blockToConTeXt (SimpleFigure attr txt (src, _)) = do capt <- inlineListToConTeXt txt img <- inlineToConTeXt (Image attr txt (src, "")) let (ident, _, _) = attr @@ -270,6 +267,7 @@ blockToConTeXt (Table _ blkCapt specs thead tbody tfoot) = do then "location=none" else "title=" <> braces captionText ) $$ body $$ "\\stopplacetable" <> blankline +blockToConTeXt (Figure attr _ body) = blockToConTeXt $ Div attr body tableToConTeXt :: PandocMonad m => Tabl -> Doc Text -> [Doc Text] -> WM m (Doc Text) diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs index 1e9f37d2f0b9..91c461d251f0 100644 --- a/src/Text/Pandoc/Writers/Custom.hs +++ b/src/Text/Pandoc/Writers/Custom.hs @@ -30,6 +30,7 @@ import Text.Pandoc.Options import Text.Pandoc.Class (PandocMonad) import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Writers.Shared +import Text.Pandoc.Shared (blocksToInlines) import qualified Foreign.Lua as Lua @@ -163,6 +164,9 @@ blockToCustom (DefinitionList items) = blockToCustom (Div attr items) = Lua.callFunc "Div" (Stringify items) (attrToMap attr) +blockToCustom (Figure attr (Caption _ cbody) content) = + Lua.callFunc "Figure" (Stringify content) (Stringify $ blocksToInlines cbody) (attrToMap attr) + -- | Convert list of Pandoc block elements to Custom. blockListToCustom :: [Block] -- ^ List of block elements -> Lua String diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index 33a6f5f0c54e..553c0cef8487 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -1,6 +1,5 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} -{-# LANGUAGE ViewPatterns #-} {- | Module : Text.Pandoc.Writers.Docbook Copyright : Copyright (C) 2006-2021 John MacFarlane @@ -188,7 +187,7 @@ blockToDocbook opts (Div (id',"section":_,_) (Header lvl (_,_,attrs) ils : xs)) -- standalone documents will include them in the template. then [("xmlns", "http://docbook.org/ns/docbook"),("xmlns:xlink", "http://www.w3.org/1999/xlink")] else [] - + -- Populate miscAttr with Header.Attr.attributes, filtering out non-valid DocBook section attributes, id, and xml:id miscAttr = filter (isSectionAttr version) attrs attribs = nsAttr <> idAttr <> miscAttr @@ -233,7 +232,7 @@ blockToDocbook _ h@Header{} = do return empty blockToDocbook opts (Plain lst) = inlinesToDocbook opts lst -- title beginning with fig: indicates that the image is a figure -blockToDocbook opts (Para [Image attr txt (src,T.stripPrefix "fig:" -> Just _)]) = do +blockToDocbook opts (SimpleFigure attr txt (src, _)) = do alt <- inlinesToDocbook opts txt let capt = if null txt then empty @@ -322,6 +321,7 @@ blockToDocbook opts (Table _ blkCapt specs thead tbody tfoot) = do return $ inTagsIndented tableType $ captionDoc $$ inTags True "tgroup" [("cols", tshow (length aligns))] ( coltags $$ head' $$ body') +blockToDocbook opts (Figure attr _ body) = blockToDocbook opts $ Div attr body hasLineBreaks :: [Inline] -> Bool hasLineBreaks = getAny . query isLineBreak . walk removeNote diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index 78d0840a4f67..a94d7c34c823 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -854,7 +854,7 @@ blockToOpenXML' opts (Plain lst) = do then withParaProp prop block else block -- title beginning with fig: indicates that the image is a figure -blockToOpenXML' opts (Para [Image attr alt (src,T.stripPrefix "fig:" -> Just tit)]) = do +blockToOpenXML' opts (SimpleFigure attr alt (src, tit)) = do setFirstPara fignum <- gets stNextFigureNum unless (null alt) $ modify $ \st -> st{ stNextFigureNum = fignum + 1 } @@ -944,6 +944,8 @@ blockToOpenXML' opts (DefinitionList items) = do l <- concat `fmap` mapM (definitionListItemToOpenXML opts) items setFirstPara return l +blockToOpenXML' opts (Figure attr _ body) = + blockToOpenXML' opts $ Div attr body definitionListItemToOpenXML :: (PandocMonad m) => WriterOptions -> ([Inline],[[Block]]) diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 602c70ebedfe..d3bd84b65d9d 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -109,9 +109,7 @@ blockToDokuWiki opts (Plain inlines) = -- title beginning with fig: indicates that the image is a figure -- dokuwiki doesn't support captions - so combine together alt and caption into alt -blockToDokuWiki opts (Para [Image attr txt (src,tgt)]) - | Just tit <- T.stripPrefix "fig:" tgt - = do +blockToDokuWiki opts (SimpleFigure attr txt (src, tit)) = do capt <- if null txt then return "" else (" " <>) `fmap` inlineListToDokuWiki opts txt @@ -223,6 +221,9 @@ blockToDokuWiki opts x@(OrderedList attribs items) = do (mapM (orderedListItemToDokuWiki opts) items) return $ vcat contents <> if T.null indent then "\n" else "" +blockToDokuWiki opts (Figure attrs _ body) = + blockToDokuWiki opts $ Div attrs body + -- TODO Need to decide how to make definition lists work on dokuwiki - I don't think there -- is a specific representation of them. -- TODO This creates double '; ; ' if there is a bullet or ordered list inside a definition list diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index 6bad37404e37..9f73e4cc9ddf 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -299,9 +299,8 @@ blockToXml :: PandocMonad m => Block -> FBM m [Content] blockToXml (Plain ss) = cMapM toXml ss -- FIXME: can lead to malformed FB2 blockToXml (Para [Math DisplayMath formula]) = insertMath NormalImage formula -- title beginning with fig: indicates that the image is a figure -blockToXml (Para [Image atr alt (src,tgt)]) - | Just tit <- T.stripPrefix "fig:" tgt - = insertImage NormalImage (Image atr alt (src,tit)) +blockToXml (SimpleFigure atr alt (src, tit)) = + insertImage NormalImage (Image atr alt (src,tit)) blockToXml (Para ss) = list . el "p" <$> cMapM toXml ss blockToXml (CodeBlock _ s) = return . spaceBeforeAfter . map (el "p" . el "code") . T.lines $ s @@ -359,6 +358,7 @@ blockToXml (Table _ blkCapt specs thead tbody tfoot) = do align_str AlignRight = "right" align_str AlignDefault = "left" blockToXml Null = return [] +blockToXml (Figure _ _ body) = cMapM blockToXml body -- Replace plain text with paragraphs and add line break after paragraphs. -- It is used to convert plain text from tight list items to paragraphs. diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index c96d4622a9ac..f0844ed8dd30 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -741,9 +741,8 @@ blockToHtmlInner opts (Para [Image attr@(_,classes,_) txt (src,tit)]) -- of the slide container inlineToHtml opts (Image attr txt (src, tit)) _ -> figure opts attr txt (src, tit) --- title beginning with fig: indicates that the image is a figure -blockToHtmlInner opts (Para [Image attr txt (s,T.stripPrefix "fig:" -> Just tit)]) = - figure opts attr txt (s,tit) +blockToHtmlInner opts (SimpleFigure attr caption (src, title)) = + figure opts attr caption (src, title) blockToHtmlInner opts (Para lst) = do contents <- inlineListToHtml opts lst case contents of @@ -1019,6 +1018,31 @@ blockToHtmlInner opts (DefinitionList lst) = do defList opts contents blockToHtmlInner opts (Table attr caption colspecs thead tbody tfoot) = tableToHtml opts (Ann.toTable attr caption colspecs thead tbody tfoot) +blockToHtml opts (Figure attrs (Caption _ captBody) body) = do + html5 <- gets stHtml5 + + htmlAttrs <- attrsToHtml opts attrs + contents <- blockListToHtml opts body + + if html5 + then do + capt <- if null captBody + then return mempty + else blockListToHtml opts captBody >>= \cb -> return $ mconcat + [ H5.figcaption cb + , nl opts ] + return $ foldl (!) H5.figure htmlAttrs $ mconcat + [nl opts, contents, nl opts, capt] + else do + capt <- if null captBody + then return mempty + else blockListToHtml opts captBody >>= \cb -> return $ + mconcat + [ (H.div ! A.class_ "figcaption") cb + , nl opts ] + + return $ foldl (!) H.div (A.class_ "float" : htmlAttrs) $ mconcat + [nl opts, contents, nl opts, capt] -- | Convert Pandoc block element to HTML. All the legwork is done by -- 'blockToHtmlInner', this just takes care of emitting the notes after diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs index 75e14714ba12..c07aae2319c9 100644 --- a/src/Text/Pandoc/Writers/Haddock.hs +++ b/src/Text/Pandoc/Writers/Haddock.hs @@ -98,8 +98,7 @@ blockToHaddock opts (Plain inlines) = do contents <- inlineListToHaddock opts inlines return $ contents <> cr -- title beginning with fig: indicates figure -blockToHaddock opts (Para [Image attr alt (src,tgt)]) - | Just tit <- T.stripPrefix "fig:" tgt +blockToHaddock opts (SimpleFigure attr alt (src, tit)) = blockToHaddock opts (Para [Image attr alt (src,tit)]) blockToHaddock opts (Para inlines) = -- TODO: if it contains linebreaks, we need to use a @...@ block @@ -150,6 +149,8 @@ blockToHaddock opts (OrderedList (start,_,delim) items) = do blockToHaddock opts (DefinitionList items) = do contents <- mapM (definitionListItemToHaddock opts) items return $ vcat contents <> blankline +blockToHaddock opts (Figure _ _ body) = + fmap (<> blankline) (blockListToHaddock opts body) -- | Convert bullet list item (list of blocks) to haddock bulletListItemToHaddock :: PandocMonad m diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs index c254fbc584cd..d9edfdd6ed9e 100644 --- a/src/Text/Pandoc/Writers/ICML.hs +++ b/src/Text/Pandoc/Writers/ICML.hs @@ -1,7 +1,6 @@ {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE ViewPatterns #-} {- | Module : Text.Pandoc.Writers.ICML @@ -309,9 +308,8 @@ blocksToICML opts style lst = do -- | Convert a Pandoc block element to ICML. blockToICML :: PandocMonad m => WriterOptions -> Style -> Block -> WS m (Doc Text) blockToICML opts style (Plain lst) = parStyle opts style "" lst --- title beginning with fig: indicates that the image is a figure -blockToICML opts style (Para img@[Image _ txt (_,Text.stripPrefix "fig:" -> Just _)]) = do - figure <- parStyle opts (figureName:style) "" img +blockToICML opts style (SimpleFigure attr txt (src, tit)) = do + figure <- parStyle opts (figureName:style) "" [Image attr txt (src, tit)] caption <- parStyle opts (imgCaptionName:style) "" txt return $ intersperseBrs [figure, caption] blockToICML opts style (Para lst) = parStyle opts (paragraphName:style) "" lst @@ -382,6 +380,8 @@ blockToICML opts style (Div (_ident, _, kvs) lst) = let dynamicStyle = maybeToList $ lookup dynamicStyleKey kvs in blocksToICML opts (dynamicStyle <> style) lst blockToICML _ _ Null = return empty +blockToICML opts style (Figure attr _ body) = + blockToICML opts style $ Div attr body -- | Convert a list of lists of blocks to ICML list items. listItemsToICML :: PandocMonad m => WriterOptions -> Text -> Style -> Maybe ListAttributes -> [[Block]] -> WS m (Doc Text) diff --git a/src/Text/Pandoc/Writers/JATS.hs b/src/Text/Pandoc/Writers/JATS.hs index 9db8723d16ec..fd47aaca5bad 100644 --- a/src/Text/Pandoc/Writers/JATS.hs +++ b/src/Text/Pandoc/Writers/JATS.hs @@ -291,9 +291,7 @@ blockToJATS opts (Header _ _ title) = do return $ inTagsSimple "title" title' -- No Plain, everything needs to be in a block-level tag blockToJATS opts (Plain lst) = blockToJATS opts (Para lst) --- title beginning with fig: indicates that the image is a figure -blockToJATS opts (Para [Image (ident,_,kvs) txt - (src,T.stripPrefix "fig:" -> Just tit)]) = do +blockToJATS opts (SimpleFigure (ident, _, kvs) txt (src, tit)) = do alt <- inlinesToJATS opts txt let (maintype, subtype) = imageMimeType src kvs let capt = if null txt @@ -375,6 +373,8 @@ blockToJATS _ b@(RawBlock f str) blockToJATS _ HorizontalRule = return empty -- not semantic blockToJATS opts (Table attr caption colspecs thead tbody tfoot) = tableToJATS opts (Ann.toTable attr caption colspecs thead tbody tfoot) +blockToJATS opts (Figure attrs _ body) = + blockToJATS opts (Div attrs body) -- | Convert a list of inline elements to JATS. inlinesToJATS :: PandocMonad m => WriterOptions -> [Inline] -> JATS m (Doc Text) diff --git a/src/Text/Pandoc/Writers/Jira.hs b/src/Text/Pandoc/Writers/Jira.hs index 1351814e9225..bdce2c7c4174 100644 --- a/src/Text/Pandoc/Writers/Jira.hs +++ b/src/Text/Pandoc/Writers/Jira.hs @@ -114,6 +114,7 @@ toJiraBlocks blocks = do Just header -> header : bodyRows Nothing -> bodyRows return $ Jira.Table rows + Figure attr _ body -> toJiraPanel attr body jiraBlocks <- mapM convert blocks return $ mconcat jiraBlocks diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index c365aebf53dc..88b5c3b085bd 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -383,10 +383,7 @@ blockToLaTeX (Div (identifier,classes,kvs) bs) = do wrapNotes <$> wrapDiv (identifier,classes,kvs) result blockToLaTeX (Plain lst) = inlineListToLaTeX lst --- title beginning with fig: indicates that the image is a figure -blockToLaTeX (Para [Image attr@(ident, _, _) txt (src,tgt)]) - | Just tit <- T.stripPrefix "fig:" tgt - = do +blockToLaTeX (SimpleFigure attr@(ident, _, _) txt (src, tit)) = do (capt, captForLof, footnotes) <- getCaption inlineListToLaTeX True txt lab <- labelFor ident let caption = "\\caption" <> captForLof <> braces capt <> lab @@ -596,6 +593,7 @@ blockToLaTeX (Header level (id',classes,_) lst) = do blockToLaTeX (Table attr blkCapt specs thead tbodies tfoot) = tableToLaTeX inlineListToLaTeX blockListToLaTeX (Ann.toTable attr blkCapt specs thead tbodies tfoot) +blockToLaTeX (Figure attr _ body) = blockToLaTeX $ Div attr body blockListToLaTeX :: PandocMonad m => [Block] -> LW m (Doc Text) blockListToLaTeX lst = diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs index 87b2d8d21db1..c9420f529f5a 100644 --- a/src/Text/Pandoc/Writers/Man.hs +++ b/src/Text/Pandoc/Writers/Man.hs @@ -170,7 +170,6 @@ blockToMan opts (Table _ blkCapt specs thead tbody tfoot) = return $ literal ".PP" $$ caption' $$ literal ".TS" $$ literal "tab(@);" $$ coldescriptions $$ colheadings' $$ vcat body $$ literal ".TE" - blockToMan opts (BulletList items) = do contents <- mapM (bulletListItemToMan opts) items return (vcat contents) @@ -183,6 +182,7 @@ blockToMan opts (OrderedList attribs items) = do blockToMan opts (DefinitionList items) = do contents <- mapM (definitionListItemToMan opts) items return (vcat contents) +blockToMan opts (Figure attrs _ body) = blockToMan opts $ Div attrs body -- | Convert bullet list item (list of blocks) to man. bulletListItemToMan :: PandocMonad m => WriterOptions -> [Block] -> StateT WriterState m (Doc Text) diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index fda2bbcefe68..44e348d74f1e 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -2,7 +2,6 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} -{-# LANGUAGE ViewPatterns #-} {- | Module : Text.Pandoc.Writers.Markdown Copyright : Copyright (C) 2006-2021 John MacFarlane @@ -23,7 +22,7 @@ module Text.Pandoc.Writers.Markdown ( import Control.Monad.Reader import Control.Monad.State.Strict import Data.Default -import Data.List (intersperse, sortOn, transpose) +import Data.List (intersperse, sortOn, transpose, union) import Data.List.NonEmpty (nonEmpty, NonEmpty(..)) import qualified Data.Map as M import Data.Maybe (fromMaybe, mapMaybe, isNothing) @@ -365,14 +364,13 @@ blockToMarkdown' opts (Plain inlines) = do _ -> inlines contents <- inlineListToMarkdown opts inlines' return $ contents <> cr --- title beginning with fig: indicates figure -blockToMarkdown' opts (Para [Image attr alt (src,tgt@(T.stripPrefix "fig:" -> Just tit))]) +blockToMarkdown' opts (SimpleFigure attr alt (src, tit)) | isEnabled Ext_raw_html opts && not (isEnabled Ext_link_attributes opts || isEnabled Ext_attributes opts) && attr /= nullAttr = -- use raw HTML (<> blankline) . literal . T.strip <$> writeHtml5String opts{ writerTemplate = Nothing } - (Pandoc nullMeta [Para [Image attr alt (src,tgt)]]) + (Pandoc nullMeta [SimpleFigure attr alt (src, tit)]) | otherwise = blockToMarkdown opts (Para [Image attr alt (src,tit)]) blockToMarkdown' opts (Para inlines) = (<> blankline) `fmap` blockToMarkdown opts (Plain inlines) @@ -591,6 +589,8 @@ blockToMarkdown' opts (OrderedList (start,sty,delim) items) = do blockToMarkdown' opts (DefinitionList items) = do contents <- inList $ mapM (definitionListItemToMarkdown opts) items return $ mconcat contents <> blankline +blockToMarkdown' opts (Figure (ident, classes, kvs) _ body) = + blockToMarkdown' opts (Div (ident, ["figure"] `union` classes, kvs) body) inList :: Monad m => MD m a -> MD m a inList p = local (\env -> env {envInList = True}) p diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index 5029be69f636..535921e20742 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -1,5 +1,4 @@ {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE ViewPatterns #-} {- | Module : Text.Pandoc.Writers.MediaWiki Copyright : Copyright (C) 2008-2021 John MacFarlane @@ -17,6 +16,7 @@ module Text.Pandoc.Writers.MediaWiki ( writeMediaWiki, highlightingLangs ) where import Control.Monad.Reader import Control.Monad.State.Strict import Data.Maybe (fromMaybe) +import qualified Data.List as DL import qualified Data.Set as Set import Data.Text (Text) import qualified Data.Text as T @@ -91,8 +91,7 @@ blockToMediaWiki (Div attrs bs) = do blockToMediaWiki (Plain inlines) = inlineListToMediaWiki inlines --- title beginning with fig: indicates that the image is a figure -blockToMediaWiki (Para [Image attr txt (src,T.stripPrefix "fig:" -> Just tit)]) = do +blockToMediaWiki (SimpleFigure attr txt (src, tit)) = do capt <- inlineListToMediaWiki txt img <- imageToMediaWiki attr let opt = if T.null tit @@ -207,6 +206,9 @@ blockToMediaWiki x@(DefinitionList items) = do contents <- local (\s -> s { listLevel = listLevel s <> ";" }) $ mapM definitionListItemToMediaWiki items return $ vcat contents <> if null lev then "\n" else "" +blockToMediaWiki (Figure (ident, classes, kvs) _ body) = + blockToMediaWiki (Div (ident, ["figure"] `DL.union` classes, kvs) body) + -- Auxiliary functions for lists: -- | Convert ordered list attributes to HTML attribute string diff --git a/src/Text/Pandoc/Writers/Ms.hs b/src/Text/Pandoc/Writers/Ms.hs index 97c23f24d46b..382a391c0c5d 100644 --- a/src/Text/Pandoc/Writers/Ms.hs +++ b/src/Text/Pandoc/Writers/Ms.hs @@ -284,7 +284,6 @@ blockToMs opts (Table _ blkCapt specs thead tbody tfoot) = then "" else ".nr LL \\n[LLold]") $$ literal ".ad" - blockToMs opts (BulletList items) = do contents <- mapM (bulletListItemToMs opts) items setFirstPara @@ -300,6 +299,7 @@ blockToMs opts (DefinitionList items) = do contents <- mapM (definitionListItemToMs opts) items setFirstPara return (vcat contents) +blockToMs opts (Figure attr _ body) = blockToMs opts $ Div attr body -- | Convert bullet list item (list of blocks) to ms. bulletListItemToMs :: PandocMonad m => WriterOptions -> [Block] -> MS m (Doc Text) diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index d5100f43fe4a..b47fbdf480bf 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -276,6 +276,7 @@ blockToMuse (Table _ blkCapt specs thead tbody tfoot) = isSimple = onlySimpleTableCells (headers : rows) && all (== 0) widths blockToMuse (Div _ bs) = flatBlockListToMuse bs blockToMuse Null = return empty +blockToMuse (Figure {}) = return empty -- | Return Muse representation of notes collected so far. currentNotesToMuse :: PandocMonad m diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index 5f3224c2fe1b..07fd3cc5a8af 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -2,7 +2,6 @@ {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} -{-# LANGUAGE ViewPatterns #-} {- | Module : Text.Pandoc.Writers.OpenDocument Copyright : Copyright (C) 2008-2020 Andrea Rossato and John MacFarlane @@ -377,7 +376,7 @@ blockToOpenDocument o = \case Plain b -> if null b then return empty else inParagraphTags =<< inlinesToOpenDocument o b - Para [Image attr c (s,T.stripPrefix "fig:" -> Just t)] -> figure attr c s t + SimpleFigure attr c (s, t) -> figure attr c s t Para b -> if null b && not (isEnabled Ext_empty_paragraphs o) then return empty @@ -399,6 +398,7 @@ blockToOpenDocument o = \case then return $ text $ T.unpack s else empty <$ report (BlockNotRendered b) Null -> return empty + Figure attrs _ body -> mkDiv attrs body where defList b = do setInDefinitionList True r <- vcat <$> mapM (deflistItemToOpenDocument o) b diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs index d404f1c8d116..a80d4adf6c4f 100644 --- a/src/Text/Pandoc/Writers/Org.hs +++ b/src/Text/Pandoc/Writers/Org.hs @@ -105,9 +105,7 @@ blockToOrg :: PandocMonad m blockToOrg Null = return empty blockToOrg (Div attr bs) = divToOrg attr bs blockToOrg (Plain inlines) = inlineListToOrg inlines --- title beginning with fig: indicates that the image is a figure -blockToOrg (Para [Image attr txt (src,tgt)]) - | Just tit <- T.stripPrefix "fig:" tgt = do +blockToOrg (SimpleFigure attr txt (src, tit)) = do capt <- if null txt then return empty else ("#+caption: " <>) `fmap` inlineListToOrg txt @@ -213,6 +211,13 @@ blockToOrg (OrderedList (start, _, delim) items) = do blockToOrg (DefinitionList items) = do contents <- mapM definitionListItemToOrg items return $ vcat contents $$ blankline +blockToOrg (Figure (ident, _, _) _ body) = do + -- Represent the figure as content that can be internally linked from other + -- parts of the document. + contents <- (if T.null ident + then id + else ("<<" <> literal ident <> ">>" $$)) <$> blockListToOrg body + return (blankline $$ contents $$ blankline) -- | Convert bullet list item (list of blocks) to Org. bulletListItemToOrg :: PandocMonad m => [Block] -> Org m (Doc Text) diff --git a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs index 10060d975f48..fed9122e7eb3 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs @@ -989,6 +989,7 @@ blockIsBlank DefinitionList ds -> all (uncurry (&&) . bimap (all inlineIsBlank) (all (all blockIsBlank))) ds Header _ _ ils -> all inlineIsBlank ils HorizontalRule -> True + Figure _ _ bls -> all blockIsBlank bls Table{} -> False Div _ bls -> all blockIsBlank bls Null -> True diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 983ef412a7fd..d5c2fe2a81dc 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -219,28 +219,34 @@ blockToRST (Div (ident,classes,_kvs) bs) = do nest 3 contents $$ blankline blockToRST (Plain inlines) = inlineListToRST inlines -blockToRST (Para [Image attr txt (src, rawtit)]) = do +blockToRST (SimpleFigure attr txt (src, tit)) = do description <- inlineListToRST txt dims <- imageDimsToRST attr - -- title beginning with fig: indicates that the image is a figure - let (isfig, tit) = case T.stripPrefix "fig:" rawtit of - Nothing -> (False, rawtit) - Just tit' -> (True, tit') - let fig | isfig = "figure:: " <> literal src - | otherwise = "image:: " <> literal src - alt | isfig = ":alt: " <> if T.null tit then description else literal tit - | null txt = empty + let fig = "figure:: " <> literal src + alt = ":alt: " <> if T.null tit then description else literal tit + capt = description + (_,cls,_) = attr + classes = case cls of + [] -> empty + ["align-right"] -> ":align: right" + ["align-left"] -> ":align: left" + ["align-center"] -> ":align: center" + _ -> ":figclass: " <> literal (T.unwords cls) + return $ hang 3 ".. " (fig $$ alt $$ classes $$ dims $+$ capt) $$ blankline +blockToRST (Para [Image attr txt (src, _)]) = do + description <- inlineListToRST txt + dims <- imageDimsToRST attr + let fig = "image:: " <> literal src + alt | null txt = empty | otherwise = ":alt: " <> description - capt | isfig = description - | otherwise = empty + capt = empty (_,cls,_) = attr classes = case cls of [] -> empty ["align-right"] -> ":align: right" ["align-left"] -> ":align: left" ["align-center"] -> ":align: center" - _ | isfig -> ":figclass: " <> literal (T.unwords cls) - | otherwise -> ":class: " <> literal (T.unwords cls) + _ -> ":class: " <> literal (T.unwords cls) return $ hang 3 ".. " (fig $$ alt $$ classes $$ dims $+$ capt) $$ blankline blockToRST (Para inlines) | LineBreak `elem` inlines = @@ -349,6 +355,17 @@ blockToRST (DefinitionList items) = do -- ensure that sublists have preceding blank line return $ blankline $$ vcat contents $$ blankline +blockToRST (Figure (ident, classes, _) _ body) = do + content <- blockListToRST body + return $ blankline $$ ( + ".. container:: float" <> space <> + literal (T.unwords (filter (/= "container") classes))) $$ + (if T.null ident + then blankline + else " :name: " <> literal ident $$ blankline) $$ + nest 3 content $$ + blankline + -- | Convert bullet list item (list of blocks) to RST. bulletListItemToRST :: PandocMonad m => [Block] -> RST m (Doc Text) bulletListItemToRST items = do @@ -402,7 +419,7 @@ blockListToRST' topLevel blocks = do toClose Header{} = False toClose LineBlock{} = False toClose HorizontalRule = False - toClose (Para [Image _ _ (_,t)]) = "fig:" `T.isPrefixOf` t + toClose SimpleFigure{} = True toClose Para{} = False toClose _ = True commentSep = RawBlock "rst" "..\n\n" diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index 063371ebc23a..195890fe80af 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -269,6 +269,8 @@ blockToRTF indent alignment (Table _ blkCapt specs thead tbody tfoot) = do else tableRowToRTF True indent aligns sizes headers rows' <- T.concat <$> mapM (tableRowToRTF False indent aligns sizes) rows return $ header' <> rows' <> rtfPar indent 0 alignment caption' +blockToRTF indent alignment (Figure attr _ body) = + blockToRTF indent alignment $ Div attr body tableRowToRTF :: PandocMonad m => Bool -> Int -> [Alignment] -> [Double] -> [[Block]] -> m Text diff --git a/src/Text/Pandoc/Writers/TEI.hs b/src/Text/Pandoc/Writers/TEI.hs index 18015259df4b..1c9f255e1346 100644 --- a/src/Text/Pandoc/Writers/TEI.hs +++ b/src/Text/Pandoc/Writers/TEI.hs @@ -191,6 +191,7 @@ blockToTEI _ HorizontalRule = return $ selfClosingTag "milestone" [("unit","undefined") ,("type","separator") ,("rendition","line")] +blockToTEI _ (Figure {}) = return empty -- | TEI Tables -- TEI Simple's tables are composed of cells and rows; other diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs index 6a33b4283561..727fba7ce6b2 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -123,14 +123,13 @@ blockToTexinfo (Plain lst) = inlineListToTexinfo lst -- title beginning with fig: indicates that the image is a figure -blockToTexinfo (Para [Image attr txt (src,tgt)]) - | Just tit <- T.stripPrefix "fig:" tgt = do +blockToTexinfo (SimpleFigure attr txt (src, tit)) = do capt <- if null txt then return empty else (\c -> text "@caption" <> braces c) `fmap` inlineListToTexinfo txt img <- inlineToTexinfo (Image attr txt (src,tit)) - return $ text "@float" $$ img $$ capt $$ text "@end float" + return $ text "@float Figure" $$ img $$ capt $$ text "@end float" blockToTexinfo (Para lst) = inlineListToTexinfo lst -- this is handled differently from Plain in blockListToTexinfo @@ -255,11 +254,39 @@ blockToTexinfo (Table _ blkCapt specs thead tbody tfoot) = do text "@end multitable" return $ if isEmpty captionText then tableBody <> blankline - else text "@float" $$ + else text "@float Table" $$ tableBody $$ inCmd "caption" captionText $$ text "@end float" +blockToTexinfo (Figure _ (Caption _ caption) [SimpleFigure attr figCaption target]) = + blockToTexinfo (SimpleFigure attr (if null figCaption + then blocksToInlines caption + else figCaption) + target) + +blockToTexinfo (Figure _ fCaption [ + Table attr tCaption@(Caption _ cbody) specs thead tbody tfoot]) = do + let caption = blocksToInlines cbody + captionText <- inlineListToTexinfo caption + blockToTexinfo (Table attr (if null captionText + then fCaption + else tCaption) + specs thead tbody tfoot) + +blockToTexinfo (Figure _ (Caption _ caption) body) = do + captionText <- inlineListToTexinfo $ blocksToInlines caption + content <- blockListToTexinfo body + return $ text ("@float" ++ floatType body) $$ content $$ ( + if isEmpty captionText + then empty + else inCmd "caption" captionText + ) $$ text "@end float" + where + floatType [SimpleFigure {}] = " Figure" + floatType [Table {}] = " Table" + floatType _ = "" + tableHeadToTexinfo :: PandocMonad m => [Alignment] -> [[Block]] diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs index 03d03047752a..7bf473a4af3b 100644 --- a/src/Text/Pandoc/Writers/Textile.hs +++ b/src/Text/Pandoc/Writers/Textile.hs @@ -1,5 +1,4 @@ {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE ViewPatterns #-} {- | Module : Text.Pandoc.Writers.Textile Copyright : Copyright (C) 2010-2021 John MacFarlane @@ -111,8 +110,7 @@ blockToTextile opts (Div attr bs) = do blockToTextile opts (Plain inlines) = inlineListToTextile opts inlines --- title beginning with fig: indicates that the image is a figure -blockToTextile opts (Para [Image attr txt (src,T.stripPrefix "fig:" -> Just tit)]) = do +blockToTextile opts (SimpleFigure attr txt (src, tit)) = do capt <- blockToTextile opts (Para txt) im <- inlineToTextile opts (Image attr txt (src,tit)) return $ im <> "\n" <> capt @@ -244,6 +242,19 @@ blockToTextile opts (DefinitionList items) = do contents <- withUseTags $ mapM (definitionListItemToTextile opts) items return $ "
\n" <> vcat contents <> "\n
\n" +blockToTextile opts (Figure attr (Caption _ caption) body) = do + let startTag = render Nothing $ tagWithAttrs "figure" attr + let endTag = "
" + let captionInlines = blocksToInlines caption + captionMarkup <- if null captionInlines + then return "" + else ((<> "\n\n\n\n") . ("
\n\n" <>)) <$> + inlineListToTextile opts (blocksToInlines caption) + contents <- blockListToTextile opts body + return $ startTag <> "\n\n" <> + captionMarkup <> + contents <> "\n\n" <> endTag <> "\n" + -- Auxiliary functions for lists: -- | Convert ordered list attributes to HTML attribute string diff --git a/src/Text/Pandoc/Writers/XWiki.hs b/src/Text/Pandoc/Writers/XWiki.hs index c352356507cb..dbcfd20bc449 100644 --- a/src/Text/Pandoc/Writers/XWiki.hs +++ b/src/Text/Pandoc/Writers/XWiki.hs @@ -122,6 +122,10 @@ blockToXWiki (DefinitionList items) = do contents <- local (\s -> s { listLevel = listLevel s <> ";" }) $ mapM definitionListItemToMediaWiki items return $ vcat contents <> if Text.null lev then "\n" else "" +blockToXWiki (Figure attr _ body) = do + content <- blockToXWiki $ Div attr body + return $ intercalate content ["(((\n", ")))"] + -- TODO: support more features blockToXWiki (Table _ blkCapt specs thead tbody tfoot) = do let (_, _, _, headers, rows') = toLegacyTable blkCapt specs thead tbody tfoot diff --git a/src/Text/Pandoc/Writers/ZimWiki.hs b/src/Text/Pandoc/Writers/ZimWiki.hs index df914f5906aa..566955d1bd15 100644 --- a/src/Text/Pandoc/Writers/ZimWiki.hs +++ b/src/Text/Pandoc/Writers/ZimWiki.hs @@ -1,5 +1,4 @@ {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE ViewPatterns #-} {- | Module : Text.Pandoc.Writers.ZimWiki Copyright : © 2008-2021 John MacFarlane, @@ -86,9 +85,8 @@ blockToZimWiki opts (Div _attrs bs) = do blockToZimWiki opts (Plain inlines) = inlineListToZimWiki opts inlines --- title beginning with fig: indicates that the image is a figure -- ZimWiki doesn't support captions - so combine together alt and caption into alt -blockToZimWiki opts (Para [Image attr txt (src,T.stripPrefix "fig:" -> Just tit)]) = do +blockToZimWiki opts (SimpleFigure attr txt (src, tit)) = do capt <- if null txt then return "" else (" " <>) `fmap` inlineListToZimWiki opts txt @@ -181,6 +179,10 @@ blockToZimWiki opts (DefinitionList items) = do contents <- mapM (definitionListItemToZimWiki opts) items return $ vcat contents +blockToZimWiki opts (Figure _ _ body) = do + contents <- blockListToZimWiki opts body + return $ contents <> "\n" + definitionListItemToZimWiki :: PandocMonad m => WriterOptions -> ([Inline],[[Block]]) diff --git a/stack.yaml b/stack.yaml index e93b6b0a756a..e0da2b95e476 100644 --- a/stack.yaml +++ b/stack.yaml @@ -13,6 +13,8 @@ extra-deps: - skylighting-0.11 - doctemplates-0.10 - texmath-0.12.3.1 +- git: https://github.com/argent0/pandoc-types + commit: 5b32019746d1692c593c080f9a8ee45c7d25ecba - git: https://github.com/jgm/citeproc.git commit: b27201c3ac48ffd2853f77152df19b6e2cf36987 ghc-options: diff --git a/test/Tests/Command.hs b/test/Tests/Command.hs index c197fd11f589..c75667b4867a 100644 --- a/test/Tests/Command.hs +++ b/test/Tests/Command.hs @@ -73,14 +73,14 @@ runTest testExePath testname cmd inp norm = testCase testname $ do else return $ TestError ec assertBool (show result) (result == TestPassed) -tests :: TestTree +tests :: FilePath -> TestTree {-# NOINLINE tests #-} -tests = unsafePerformIO $ do +tests root = unsafePerformIO $ do files <- filter (".md" `isSuffixOf`) <$> - getDirectoryContents "command" + getDirectoryContents root testExePath <- getExecutablePath - let cmds = map (extractCommandTest testExePath) files - return $ testGroup "Command:" cmds + let cmds = map (extractCommandTest root testExePath) files + return $ testGroup ("Command folder: " <> root) cmds isCodeBlock :: Block -> Bool isCodeBlock (CodeBlock _ _) = True @@ -94,9 +94,9 @@ dropPercent :: String -> String dropPercent ('%':xs) = dropWhile (== ' ') xs dropPercent xs = xs -runCommandTest :: FilePath -> FilePath -> Int -> String -> TestTree -runCommandTest testExePath fp num code = - goldenTest testname getExpected getActual compareValues' updateGolden +runCommandTest :: FilePath -> FilePath -> FilePath -> Int -> String -> TestTree +runCommandTest root testExePath fp num code = + goldenTest testname getExpected getActual compareValues updateGolden where testname = "#" <> show num codelines = lines code @@ -109,13 +109,13 @@ runCommandTest testExePath fp num code = norm = unlines normlines getExpected = return norm getActual = snd <$> execTest testExePath cmd input - compareValues' expected actual + compareValues expected actual | actual == expected = return Nothing - | otherwise = return $ Just $ "--- test/command/" ++ fp ++ "\n+++ " ++ + | otherwise = return $ Just $ "--- test" root fp ++ "\n+++ " ++ cmd ++ "\n" ++ showDiff (1,1) (getDiff (lines actual) (lines expected)) updateGolden newnorm = do - let fp' = "command" fp + let fp' = "command/figures" fp raw <- UTF8.readFile fp' let cmdline = "% " <> cmd let x = cmdline <> "\n" <> input <> "^D\n" <> norm @@ -123,13 +123,13 @@ runCommandTest testExePath fp num code = let updated = T.replace (T.pack x) (T.pack y) raw UTF8.writeFile fp' updated -extractCommandTest :: FilePath -> FilePath -> TestTree -extractCommandTest testExePath fp = unsafePerformIO $ do - contents <- UTF8.toText <$> BS.readFile ("command" fp) +extractCommandTest :: FilePath -> FilePath -> FilePath -> TestTree +extractCommandTest root testExePath fp = unsafePerformIO $ do + contents <- UTF8.toText <$> BS.readFile (root fp) Pandoc _ blocks <- runIOorExplode (readMarkdown def{ readerExtensions = pandocExtensions } contents) let codeblocks = map extractCode $ filter isCodeBlock blocks - let cases = zipWith (runCommandTest testExePath fp) [1..] codeblocks + let cases = zipWith (runCommandTest root testExePath fp) [1..] codeblocks return $ testGroup fp $ if null cases then [testCase "!!" $ assertFailure "No command tests defined"] diff --git a/test/command/figures/figures-fb2.md b/test/command/figures/figures-fb2.md new file mode 100644 index 000000000000..63aa86dc9692 --- /dev/null +++ b/test/command/figures/figures-fb2.md @@ -0,0 +1,8 @@ +``` +% pandoc -f native -t fb2 +[Figure ("fig-id",[],[]) (Caption Nothing []) [Para [Str "content"]]] + +^D + +unrecognisedpandoc<p />

content

+``` diff --git a/test/command/figures/figures-haddock.md b/test/command/figures/figures-haddock.md new file mode 100644 index 000000000000..9a63861d77f8 --- /dev/null +++ b/test/command/figures/figures-haddock.md @@ -0,0 +1,7 @@ +``` +% pandoc -f native -t haddock +[Figure ("fig-id",[],[]) (Caption Nothing []) [Para [Str "content"]]] + +^D +content +``` diff --git a/test/command/figures/figures-html.md b/test/command/figures/figures-html.md new file mode 100644 index 000000000000..f80f4c4e930f --- /dev/null +++ b/test/command/figures/figures-html.md @@ -0,0 +1,78 @@ +# Writer + +HTML5 figure with caption and content. + +``` +% pandoc -f native -t html5 +[Figure ("fig-id",[],[]) (Caption Nothing [Plain [Str "caption"]]) [Para [Str "content"]]] + +^D +
+

content

+
caption
+
+``` + +HTML5 figure with NO caption and content. + +``` +% pandoc -f native -t html5 +[Figure ("fig-id",[],[]) (Caption Nothing []) [Para [Str "content"]]] + +^D +
+

content

+
+``` + +HTML4 figure with caption and content. + +``` +% pandoc -f native -t html4 +[Figure ("fig-id",[],[]) (Caption Nothing [Plain [Str "caption"]]) [Para [Str "content"]]] + +^D +
+

content

+
caption
+
+``` + +HTML4 figure with NO caption and content. + +``` +% pandoc -f native -t html4 +[Figure ("fig-id",[],[]) (Caption Nothing []) [Para [Str "content"]]] + +^D +
+

content

+
+``` + +# Reader + +Figure with caption and multiple elements. + +``` +% pandoc -f html+native_figures -t native +
+ +
  • ITEM
+
CAP2
+
+^D +[Figure ("",["important"],[]) (Caption Nothing [Plain [Str "CAP2"]]) [Plain [Image ("",[],[]) [] ("../media/rId25.jpg","")],BulletList [[Plain [Str "ITEM"]]]]] +``` + +Figure without caption. + +``` +% pandoc -f html+native_figures -t native +
+ +
  • ITEM
+
+^D +[Figure ("",["important"],[]) (Caption Nothing []) [Plain [Image ("",[],[]) [] ("../media/rId25.jpg","")],BulletList [[Plain [Str "ITEM"]]]]] +``` diff --git a/test/command/figures/figures-jats.md b/test/command/figures/figures-jats.md new file mode 100644 index 000000000000..0f3c297f9185 --- /dev/null +++ b/test/command/figures/figures-jats.md @@ -0,0 +1,15 @@ +Figure float with caption at the figure level. + +``` +% pandoc -f native -t jats +[Figure ("fig-id",[],[]) (Caption Nothing [Para [Str "Caption"]]) [Para [Str "Text"], +Para [Image ("fig-id-2",[],[]) [] ("foo.png", "fig:")]]] + +^D + +

Text

+ + + +
+``` diff --git a/test/command/figures/figures-jira.md b/test/command/figures/figures-jira.md new file mode 100644 index 000000000000..03c8a508fcba --- /dev/null +++ b/test/command/figures/figures-jira.md @@ -0,0 +1,9 @@ +A figure with title +``` +pandoc -f native -t jira +[Figure ("fig-id",[],[("title","This is the title")]) (Caption Nothing []) []] +^D +{panel:title=This is the title} +{anchor:fig-id} +{panel} +``` diff --git a/test/command/figures/figures-latex.md b/test/command/figures/figures-latex.md new file mode 100644 index 000000000000..ee6661a3013c --- /dev/null +++ b/test/command/figures/figures-latex.md @@ -0,0 +1,45 @@ +# Figure with one image, caption and label + +``` +pandoc -f latex+native_figures -t native +\begin{document} + \begin{figure} + \includegraphics{../../media/rId25.jpg} + \caption{CAP} + \label{LAB} + \end{figure} +\end{document} +^D +[Figure ("LAB",[],[]) (Caption Nothing [Plain [Str "CAP"]]) [Plain [Image ("",[],[]) [] ("../../media/rId25.jpg","")]]] +``` + +# Nested figures + +``` +pandoc -f latex+native_figures -t native +\begin{figure} + \begin{subfigure}[b]{0.5\textwidth} + \begin{subfigure}[b]{0.5\textwidth} + \centering + \includegraphics{test/media/rId25.jpg} + \caption{CAP1.1} + \end{subfigure} + \begin{subfigure}[b]{0.5\textwidth} + \centering + \includegraphics{test/media/rId25.jpg} + \caption{CAP1.2} + \end{subfigure} + \caption{CAP1} + \label{fig:inner1} + \end{subfigure} + \begin{subfigure}[b]{0.5\textwidth} + \includegraphics{test/media/rId25.jpg} + \caption{CAP2} + \label{fig:inner2} + \end{subfigure} + \caption{CAP} + \label{fig:outer} +\end{figure} +^D +[Figure ("fig:outer",[],[]) (Caption Nothing [Plain [Str "CAP"]]) [Figure ("fig:inner1",[],[]) (Caption Nothing [Plain [Str "CAP1"]]) [Figure ("",[],[]) (Caption Nothing [Plain [Str "CAP1.1"]]) [Plain [Image ("",[],[]) [] ("test/media/rId25.jpg","")]],Figure ("",[],[]) (Caption Nothing [Plain [Str "CAP1.2"]]) [Plain [Image ("",[],[]) [] ("test/media/rId25.jpg","")]]],Figure ("fig:inner2",[],[]) (Caption Nothing [Plain [Str "CAP2"]]) [Plain [Image ("",[],[]) [] ("test/media/rId25.jpg","")]]]] +``` diff --git a/test/command/figures/figures-markdown.md b/test/command/figures/figures-markdown.md new file mode 100644 index 000000000000..ef5b06682d03 --- /dev/null +++ b/test/command/figures/figures-markdown.md @@ -0,0 +1,11 @@ +Figure float with caption at the figure level. + +``` +% pandoc -f native -t markdown +[Figure ("fig-id",[],[]) (Caption Nothing [Para [Str "Caption"]]) [Para [Image ("",[],[]) [] ("foo.png", "fig:")]]] + +^D +::: {#fig-id .figure} +![](foo.png) +::: +``` diff --git a/test/command/figures/figures-mediawiki.md b/test/command/figures/figures-mediawiki.md new file mode 100644 index 000000000000..63bb2a96d8c1 --- /dev/null +++ b/test/command/figures/figures-mediawiki.md @@ -0,0 +1,14 @@ +Figure float with caption at the figure level. + +``` +% pandoc -f native -t mediawiki +[Figure ("fig-id",[],[]) (Caption Nothing [Para [Str "Caption"]]) [Para [Image ("",[],[]) [] ("foo.png", "fig:")]]] + +^D +
+ +[[File:foo.png|thumb|none]] + + +
+``` diff --git a/test/command/figures/figures-org.md b/test/command/figures/figures-org.md new file mode 100644 index 000000000000..bfa5c6de162c --- /dev/null +++ b/test/command/figures/figures-org.md @@ -0,0 +1,16 @@ +``` +% pandoc -f native -t org +[Figure ("fig-id",[],[]) (Caption Nothing []) [Para [Str "content"]]] + +^D +<> +content +``` + +``` +% pandoc -f native -t org +[Figure ("",[],[]) (Caption Nothing []) [Para [Str "content"]]] + +^D +content +``` diff --git a/test/command/figures/figures-rst.md b/test/command/figures/figures-rst.md new file mode 100644 index 000000000000..5e84ec891169 --- /dev/null +++ b/test/command/figures/figures-rst.md @@ -0,0 +1,13 @@ +Figure float with caption at the figure level. + +``` +% pandoc -f native -t rst +[Figure ("fig-id",[],[]) (Caption Nothing [Para [Str "Caption"]]) [Para [Image ("",[],[]) [] ("foo.png", "fig:")]]] + +^D +.. container:: float + :name: fig-id + + .. figure:: foo.png + :alt: +``` diff --git a/test/command/figures/figures-texinfo.md b/test/command/figures/figures-texinfo.md new file mode 100644 index 000000000000..f5d42de7d626 --- /dev/null +++ b/test/command/figures/figures-texinfo.md @@ -0,0 +1,115 @@ +Figure float with caption at the figure level. + +``` +% pandoc -f native -t texinfo +[Figure ("fig-id",[],[]) (Caption Nothing [Para [Str "Caption"]]) [Para [Image ("",[],[]) [] ("foo.png", "fig:")]]] + +^D +@node Top +@top Top + +@float Figure +@image{foo,,,Caption,png} +@caption{Caption} +@end float +``` + +Float that has no caption and doesn't contain a `SimpleFigure` + +``` +% pandoc -f native -t texinfo +[Figure ("fig-id",[],[]) (Caption Nothing []) [Para [Image ("",[],[]) [] ("foo.png", "")]]] + +^D +@node Top +@top Top + +@float +@image{foo,,,,png} +@end float +``` + +Table float with caption at the figure level. + +``` +% pandoc -f native -t texinfo +[Figure ("fig-id",[],[]) (Caption Nothing [Para [Str "Caption"]]) +[Table ("",[],[]) (Caption Nothing + []) + [(AlignDefault,ColWidthDefault) + ,(AlignDefault,ColWidthDefault) + ,(AlignDefault,ColWidthDefault)] + (TableHead ("",[],[]) + [Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "Fruit"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "Price"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "Quantity"]]]]) + [(TableBody ("",[],[]) (RowHeadColumns 0) + [] + [Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "Apple"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "25",Space,Str "cents"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "33"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "\"Navel\"",Space,Str "Orange"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "35",Space,Str "cents"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "22"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "45"]]]])] + (TableFoot ("",[],[]) + [])]] + +^D +@node Top +@top Top + +@float Table +@multitable {"Navel" Orange} {35 cents} {Quantity} +@headitem +Fruit + @tab Price + @tab Quantity +@item +Apple + @tab 25 cents + @tab 33 +@item +"Navel" Orange + @tab 35 cents + @tab 22 +@item +45 +@end multitable +@caption{Caption} +@end float +``` + +Float the isn't a table nor a figure. + +``` +% pandoc -f native -t texinfo +[Figure ("fig-id",[],[]) (Caption Nothing [Para[ Str "Caption"]]) [Para [Str "Content"]]] + +^D +@node Top +@top Top + +@float +Content +@caption{Caption} +@end float +``` diff --git a/test/command/figures/figures-textile.md b/test/command/figures/figures-textile.md new file mode 100644 index 000000000000..27c60cbe866f --- /dev/null +++ b/test/command/figures/figures-textile.md @@ -0,0 +1,31 @@ +``` +% pandoc -f native -t textile +[Figure ("fig-id",[],[]) (Caption Nothing [Para [Str "Caption"]]) [Para [Image ("",[],[]) [] ("foo.png", "")]]] + +^D +
+ +
+ +Caption + +
+ +!foo.png! + + +
+``` + +``` +% pandoc -f native -t textile +[Figure ("fig-id",[],[]) (Caption Nothing []) [Para [Image ("",[],[]) [] ("foo.png", "")]]] + +^D +
+ +!foo.png! + + +
+``` diff --git a/test/command/figures/figures-xwiki.md b/test/command/figures/figures-xwiki.md new file mode 100644 index 000000000000..c4fea0483df3 --- /dev/null +++ b/test/command/figures/figures-xwiki.md @@ -0,0 +1,9 @@ +``` +% pandoc -f native -t xwiki +[Figure ("fig-id",[],[]) (Caption Nothing []) [Para [Str "content"]]] + +^D +((( +{{id name="fig-id" /}}content +))) +``` diff --git a/test/command/figures/figures-zimwiki.md b/test/command/figures/figures-zimwiki.md new file mode 100644 index 000000000000..a2d4bcd9a413 --- /dev/null +++ b/test/command/figures/figures-zimwiki.md @@ -0,0 +1,9 @@ +``` +% pandoc -f native -t zimwiki +[Figure ("fig-id",[],[]) (Caption Nothing []) [Para [Str "content"]]] + +^D +content + + +``` diff --git a/test/command/jats-figure-alt-text.md b/test/command/jats-figure-alt-text.md new file mode 100644 index 000000000000..877999674cfc --- /dev/null +++ b/test/command/jats-figure-alt-text.md @@ -0,0 +1,12 @@ +``` +% pandoc -f jats -t native + + +

bar

+ + alternative-decription + +
+^D +[Para [Image ("fig-1",[],[("alt","alternative-decription")]) [Str "bar"] ("foo.png","fig:")]] +``` diff --git a/test/tables.texinfo b/test/tables.texinfo index 4f09246afd40..3b284e36c9b1 100644 --- a/test/tables.texinfo +++ b/test/tables.texinfo @@ -3,7 +3,7 @@ Simple table with caption: -@float +@float Table @multitable {Right} {Left} {Center} {Default} @headitem Right @@ -55,7 +55,7 @@ Right Simple table indented two spaces: -@float +@float Table @multitable {Right} {Left} {Center} {Default} @headitem Right @@ -82,7 +82,7 @@ Right @end float Multiline table with caption: -@float +@float Table @multitable @columnfractions 0.15 0.14 0.16 0.35 @headitem Centered Header diff --git a/test/test-pandoc.hs b/test/test-pandoc.hs index 476762aac620..cf55d5e1da59 100644 --- a/test/test-pandoc.hs +++ b/test/test-pandoc.hs @@ -54,7 +54,8 @@ import Text.Pandoc.Shared (inDirectory) tests :: FilePath -> TestTree tests pandocPath = testGroup "pandoc tests" - [ Tests.Command.tests + [ Tests.Command.tests "command" + , Tests.Command.tests "command/figures" , testGroup "Old" (Tests.Old.tests pandocPath) , testGroup "Shared" Tests.Shared.tests , testGroup "Writers" diff --git a/test/writer.texinfo b/test/writer.texinfo index 53a25d5151e6..622cc2934755 100644 --- a/test/writer.texinfo +++ b/test/writer.texinfo @@ -997,7 +997,7 @@ or here: @anchor{#images} From ``Voyage dans la Lune'' by Georges Melies (1902): -@float +@float Figure @image{lalune,,,lalune,jpg} @caption{lalune} @end float