diff options
| author | Albert Krewinkel <[email protected]> | 2022-12-12 11:37:27 +0100 |
|---|---|---|
| committer | John MacFarlane <[email protected]> | 2023-01-13 09:13:27 -0800 |
| commit | 909ced5153e2c7cefd5018c39f83231824940fb8 (patch) | |
| tree | c3f71e16fdd11d8fd79125e13ecd216f9cfe27b2 | |
| parent | 8a1030078537ce2d55fa6208497884828473c67e (diff) | |
Support complex figures. [API change]
Thanks and credit go to Aner Lucero, who laid the groundwork for this
feature in the 2021 GSoC project. He contributed many changes, including
modifications to the readers for HTML, JATS, and LaTeX, and to the HTML
and JATS writers.
Shared (Albert Krewinkel):
- The new function `figureDiv`, exported from `Text.Pandoc.Shared`,
offers a standardized way to convert a figure into a Div element.
Readers (Aner Lucero):
- HTML reader: `<figure>` elements are parsed as figures, with the
caption taken from the respective `<figcaption>` elements.
- JATS reader: The `<fig>` and `<caption>` elements are parsed into
figure elements, even if the contents is more complex.
- LaTeX reader: support for figures with non-image contents and for
subfigures.
- Markdown reader: paragraphs containing just an image are treated as
figures if the `implicit_figures` extension is enabled. The identifier
is used as the figure's identifier and the image description is also
used as figure caption; all other attributes are treated as belonging
to the image.
Writers (Aner Lucero, Albert Krewinkel):
- DokuWiki, Haddock, Jira, Man, MediaWiki, Ms, Muse, PPTX, RTF, TEI,
ZimWiki writers: Figures are rendered like Div elements.
- Asciidoc writer: The figure contents is unwrapped; each image in the
the figure becomes a separate figure.
- Classic custom writers: Figures are passed to the global function
`Figure(caption, contents, attr)`, where `caption` and `contents` are
strings and `attr` is a table of key-value pairs.
- ConTeXt writer: Figures are wrapped in a "placefigure" environment
with `\startplacefigure`/`\endplacefigure`, adding the features
caption and listing title as properties. Subfigures are place in a
single row with the `\startfloatcombination` environment.
- DocBook writer: Uses `mediaobject` elements, unless the figure contains
subfigures or tables, in which case the figure content is unwrapped.
- Docx writer: figures with multiple content blocks are rendered as
tables with style `FigureTable`; like before, single-image figures are
still output as paragraphs with style `Figure` or `Captioned Figure`,
depending on whether a caption is attached.
- DokuWiki writer: Caption and "alt-text" are no longer combined. The
alt text of a figure will now be lost in the conversion.
- FB2 writer: The figure caption is added as alt text to the images in
the figure; pre-existing alt texts are kept.
- ICML writer: Only single-image figures are supported. The contents of
figures with additional elements gets unwrapped.
- HTML writer: the alt text is no longer constructed from the caption,
as was the case with implicit figures. This reduces duplication, but
comes at the risk of images that are missing alt texts. Authors should
take care to provide alt texts for all images.
Some readers, most notably the Markdown reader with the
`implicit_figures` extension, add a caption that's identical to the
image description. The writer checks for this and adds an
`aria-hidden` attribute to the `<figcaption>` element in that case.
- JATS writer: The `<fig>` and `<caption>` elements are used write
figures.
- LaTeX writer: complex figures, e.g. with non-image contents and
subfigures, are supported. The `subfigure` template variable is set if
the document contains subfigures, triggering the conditional loading
of the *subcaption* package. Contants of figures that contain tables
are become unwrapped, as longtable environments are not allowed within
figures.
- Markdown writer: figures are output as implicit figures if possible,
via HTML if the `raw_html` extension is enabled, and as Div elements
otherwise.
- OpenDocument writer: A separate paragraph is generated for each block
element in a figure, each with style `FigureWithCaption`. Behavior for
single-image figures therefore remains unchanged.
- Org writer: Only the first element in a figure is given a caption;
additional block elements in the figure are appended without any
caption being added.
- RST writer: Single-image figures are supported as before; the contents
of more complex images become nested in a container of type `float`.
- Texinfo writer: Figures are rendered as float with type `figure`.
- Textile writer: Figures are rendered with the help of HTML elements.
- XWiki: Figures are placed in a group.
Co-authored-by: Aner Lucero <[email protected]>
98 files changed, 1492 insertions, 595 deletions
diff --git a/cabal.project b/cabal.project index 1bf9697e4..d9b2dd020 100644 --- a/cabal.project +++ b/cabal.project @@ -16,3 +16,13 @@ source-repository-package type: git location: https://github.com/jgm/texmath tag: 1a77db688bd3285228299e5aeefc93d6c0d8c0b9 + +source-repository-package + type: git + location: https://github.com/tarleb/pandoc-types + tag: f84b7359765a2798f22efe4e9457538cda7a8d4a + +source-repository-package + type: git + location: https://github.com/pandoc/pandoc-lua-marshal + tag: a2a97e2af78326ea7841101d4ef56e74426b66c4 diff --git a/data/templates/default.latex b/data/templates/default.latex index 68a006971..16ea51e03 100644 --- a/data/templates/default.latex +++ b/data/templates/default.latex @@ -293,6 +293,9 @@ $if(numbersections)$ $else$ \setcounter{secnumdepth}{-\maxdimen} % remove section numbering $endif$ +$if(subfigure)$ +\usepackage{subcaption} +$endif$ $if(beamer)$ $else$ $if(block-headings)$ diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer/Classic.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer/Classic.hs index 6701efdc3..19f5ad154 100644 --- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer/Classic.hs +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer/Classic.hs @@ -157,6 +157,12 @@ blockToCustom (CodeBlock attr str) = blockToCustom (BlockQuote blocks) = invoke "BlockQuote" (Stringify blocks) +blockToCustom (Figure attr (Caption _ cbody) content) = + invoke "Figure" + (Stringify cbody) + (Stringify content) + (attrToMap attr) + blockToCustom (Table _ blkCapt specs thead tbody tfoot) = let (capt, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot aligns' = map show aligns diff --git a/pandoc-lua-engine/test/sample.lua b/pandoc-lua-engine/test/sample.lua index aacc0d2b6..0294cfbaf 100644 --- a/pandoc-lua-engine/test/sample.lua +++ b/pandoc-lua-engine/test/sample.lua @@ -295,6 +295,12 @@ function CaptionedImage(src, tit, caption, attr) end end +function Figure(caption, contents, attr) + return '<figure' .. attributes(attr) .. '>\n' .. contents .. + '\n<figcaption>' .. caption .. '</figcaption>\n' .. + '</figure>' +end + -- Caption is a string, aligns is an array of strings, -- widths is an array of floats, headers is an array of -- strings, rows is an array of arrays of strings. diff --git a/pandoc-lua-engine/test/writer.custom b/pandoc-lua-engine/test/writer.custom index eb53363fa..aaeefdd51 100644 --- a/pandoc-lua-engine/test/writer.custom +++ b/pandoc-lua-engine/test/writer.custom @@ -737,7 +737,8 @@ So is ‘pine.’</p> <p>From “Voyage dans la Lune” by Georges Melies (1902):</p> <figure> -<img src="lalune.jpg" id="" alt="lalune"/><figcaption>lalune</figcaption> +<img src="lalune.jpg" title="Voyage dans la Lune"/> +<figcaption>lalune</figcaption> </figure> <p>Here is a movie <img src="movie.jpg" title=""/> icon.</p> diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index f033b8e92..3083ffcd3 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -25,7 +25,7 @@ module Text.Pandoc.Readers.HTML ( readHtml ) where import Control.Applicative ((<|>)) -import Control.Monad (guard, msum, mzero, unless, void) +import Control.Monad (guard, mzero, unless, void) import Control.Monad.Except (throwError, catchError) import Control.Monad.Reader (ask, asks, lift, local, runReaderT) import Data.Text.Encoding.Base64 (encodeBase64) @@ -36,6 +36,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) @@ -63,8 +64,8 @@ import Text.Pandoc.Options ( extensionEnabled) import Text.Pandoc.Parsing hiding ((<|>)) import Text.Pandoc.Shared ( - addMetaField, blocksToInlines', extractSpaces, - htmlSpanLikeElements, renderTags', safeRead, tshow, formatCode) + addMetaField, extractSpaces, htmlSpanLikeElements, renderTags', + safeRead, tshow, formatCode) import Text.Pandoc.URI (escapeURI) import Text.Pandoc.Walk import Text.TeXMath (readMathML, writeTeX) @@ -581,24 +582,15 @@ 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.simpleFigureWith attr caption url tit - _ -> mzero +pFigure = do + TagOpen tag attrList <- pSatisfy $ matchTagOpen "figure" [] + let parser = Left <$> pInTags "figcaption" block <|> + (Right <$> block) + (captions, rest) <- partitionEithers <$> manyTill parser (pCloses tag <|> eof) + -- Concatenate all captions together + return $ B.figureWith (toAttr attrList) + (B.simpleCaption (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 643c92242..fbf46a339 100644 --- a/src/Text/Pandoc/Readers/JATS.hs +++ b/src/Text/Pandoc/Readers/JATS.hs @@ -38,7 +38,6 @@ import Text.TeXMath (readMathML, writeTeX) 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 @@ -232,29 +231,17 @@ parseBlock (Elem e) = terms' <- mapM getInlines terms items' <- mapM getBlocks items return (mconcat $ intersperse (str "; ") terms', items') - parseFigure = - -- if a simple caption and single graphic, we emit a standard - -- implicit figure. otherwise, we emit a div with the contents - case filterChildren (named "graphic") e of - [g] -> do - capt <- case filterChild (named "caption") e of - Just t -> mconcat . - intersperse linebreak <$> - mapM getInlines - (filterChildren (const True) t) - Nothing -> return mempty - - 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 + parseFigure = do + capt <- case filterChild (named "caption") e of + Just t -> mconcat . intersperse linebreak <$> + mapM getInlines (filterChildren (const True) t) + Nothing -> return mempty + contents <- getBlocks e + + return $ figureWith + (attrValue "id" e, [], []) + (simpleCaption $ plain capt) + contents parseFootnoteGroup = do forM_ (filterChildren (named "fn") e) $ \fn -> do let id' = attrValue "id" fn diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index 9ee3dea21..39386843f 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -33,6 +33,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) @@ -1011,8 +1012,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 *> figure') + , ("subfigure", env "subfigure" $ skipopts *> tok *> figure') , ("center", divWith ("", ["center"], []) <$> env "center" blocks) , ("quote", blockQuote <$> env "quote" blocks) , ("quotation", blockQuote <$> env "quotation" blocks) @@ -1164,37 +1165,33 @@ letterContents = do _ -> mempty return $ addr <> bs -- sig added by \closing -figure :: PandocMonad m => LP m Blocks -figure = try $ do +figure' :: PandocMonad m => LP m Blocks +figure' = try $ do resetCaption - blocks >>= addImageCaption - -addImageCaption :: PandocMonad m => Blocks -> LP m Blocks -addImageCaption = walkM go - where go p@(Para [Image attr@(_, cls, kvs) _ (src, tit)]) - | not ("fig:" `T.isPrefixOf` tit) = do - st <- getState - case sCaption st of - Nothing -> return p - Just (Caption _mbshort bs) -> do - let mblabel = sLastLabel st - let attr' = case mblabel 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' - (maybe id removeLabel mblabel - (blocksToInlines bs)) - (src, tit) - go x = return x + innerContent <- many $ try (Left <$> label) <|> (Right <$> block) + let content = walk go $ mconcat $ snd $ partitionEithers innerContent + st <- getState + let caption' = case sCaption st of + Nothing -> B.emptyCaption + Just capt -> capt + let mblabel = sLastLabel st + let attr = case mblabel of + Just lab -> (lab, [], []) + Nothing -> nullAttr + case mblabel of + Nothing -> pure () + Just lab -> do + num <- getNextNumber sLastFigureNum + setState + st { sLastFigureNum = num + , sLabels = M.insert lab [Str (renderDottedNum num)] (sLabels st) + } + return $ B.figureWith attr caption' 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 coloredBlock :: PandocMonad m => Text -> LP m Blocks coloredBlock stylename = try $ do diff --git a/src/Text/Pandoc/Readers/LaTeX/Math.hs b/src/Text/Pandoc/Readers/LaTeX/Math.hs index 6eb57c178..7b0437109 100644 --- a/src/Text/Pandoc/Readers/LaTeX/Math.hs +++ b/src/Text/Pandoc/Readers/LaTeX/Math.hs @@ -214,7 +214,8 @@ addQed bs = qedSign = B.str "\xa0\x25FB" italicize :: Block -> Block -italicize x@(Para [Image{}]) = x -- see #6925 +italicize x@(Para [Image{}]) = x -- see #6925 +italicize x@(Plain [Image{}]) = x -- ditto italicize (Para ils) = Para [Emph ils] italicize (Plain ils) = Plain [Emph ils] italicize x = x diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index d3a236571..776eecd62 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -1046,7 +1046,7 @@ para = try $ do [Image attr figCaption (src, tit)] | extensionEnabled Ext_implicit_figures exts , not (null figCaption) -> do - B.simpleFigureWith attr (B.fromList figCaption) src tit + implicitFigure attr (B.fromList figCaption) src tit _ -> constr inlns @@ -1077,6 +1077,17 @@ para = try $ do plain :: PandocMonad m => MarkdownParser m (F Blocks) plain = fmap B.plain . trimInlinesF <$> inlines1 +implicitFigure :: Attr -> Inlines -> Text -> Text -> Blocks +implicitFigure (ident, classes, attribs) capt url title = + let alt = case "alt" `lookup` attribs of + Just alt' -> B.text alt' + _ -> capt + attribs' = filter ((/= "alt") . fst) attribs + figattr = (ident, mempty, mempty) + caption = B.simpleCaption $ B.plain capt + figbody = B.plain $ B.imageWith ("", classes, attribs') url title alt + in B.figureWith figattr caption figbody + -- -- raw html -- diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs index c8e75e383..4dcf56b22 100644 --- a/src/Text/Pandoc/Readers/Org/Blocks.hs +++ b/src/Text/Pandoc/Readers/Org/Blocks.hs @@ -489,15 +489,10 @@ figure = try $ do figKeyVals = blockAttrKeyValues figAttrs attr = (figLabel, mempty, figKeyVals) in if isFigure - then (\c -> - B.simpleFigureWith - attr c imgSrc (unstackFig figName)) <$> figCaption + then (\c -> B.figureWith attr (B.simpleCaption (B.plain c)) + (B.plain $ B.image imgSrc figName mempty)) + <$> 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 d2a3b8db0..560e35f40 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -19,7 +19,7 @@ import Control.Monad (forM_, guard, liftM, mplus, mzero, when) import Control.Monad.Except (throwError) import Control.Monad.Identity (Identity (..)) import Data.Char (isHexDigit, isSpace, toUpper, isAlphaNum) -import Data.List (deleteFirstsBy, elemIndex, nub, sort, transpose) +import Data.List (deleteFirstsBy, elemIndex, nub, partition, sort, transpose) import qualified Data.Map as M import Data.Maybe (fromMaybe, maybeToList, isJust) import Data.Sequence (ViewR (..), viewr) @@ -730,8 +730,12 @@ directive' = do "figure" -> do (caption, legend) <- parseFromString' extractCaption body' let src = escapeURI $ trim top - return $ B.simpleFigureWith - (imgAttr "figclass") caption src "" <> legend + let (ident, cls, kvs) = imgAttr "class" + let (figclasskv, kvs') = partition ((== "figclass") . fst) kvs + let figattr = ("", concatMap (T.words . snd) figclasskv, []) + let capt = B.caption Nothing (B.plain caption <> legend) + return $ B.figureWith figattr capt $ + B.plain (B.imageWith (ident, cls, kvs') src "" (B.text src)) "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 b021db3c3..bbd0f3d18 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -47,6 +47,7 @@ module Text.Pandoc.Shared ( compactify, compactifyDL, linesToPara, + figureDiv, makeSections, uniqueIdent, inlineListToIdentifier, @@ -90,7 +91,8 @@ import Data.Containers.ListUtils (nubOrd) import Data.Char (isAlpha, isLower, isSpace, isUpper, toLower, isAlphaNum, generalCategory, GeneralCategory(NonSpacingMark, SpacingCombiningMark, EnclosingMark, ConnectorPunctuation)) -import Data.List (find, intercalate, intersperse, sortOn, foldl', groupBy) +import Data.List (find, foldl', groupBy, intercalate, intersperse, + union, sortOn) import qualified Data.Map as M import Data.Maybe (mapMaybe, fromMaybe) import Data.Monoid (Any (..)) @@ -427,6 +429,23 @@ combineLines = intercalate [LineBreak] linesToPara :: [[Inline]] -> Block linesToPara = Para . combineLines +-- | Creates a Div block from figure components. The intended use is in +-- writers of formats that do not have markup support for figures. +-- +-- The resulting div is given the class @figure@ and contains the figure +-- body and the figure caption. The latter is wrapped in a 'Div' of +-- class @caption@, with the stringified @short-caption@ as attribute. +figureDiv :: Attr -> Caption -> [Block] -> Block +figureDiv (ident, classes, kv) (Caption shortcapt longcapt) body = + let divattr = ( ident + , ["figure"] `union` classes + , kv + ) + captkv = maybe mempty (\s -> [("short-caption", stringify s)]) shortcapt + capt = [Div ("", ["caption"], captkv) longcapt | not (null longcapt)] + in Div divattr (body ++ capt) + +-- | Returns 'True' iff the given element is a 'Para'. isPara :: Block -> Bool isPara (Para _) = True isPara _ = False @@ -830,6 +849,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 7d378bbbf..29b6ff971 100644 --- a/src/Text/Pandoc/Writers/AsciiDoc.hs +++ b/src/Text/Pandoc/Writers/AsciiDoc.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} {- | Module : Text.Pandoc.Writers.AsciiDoc @@ -29,6 +30,7 @@ import Data.Maybe (fromMaybe, isJust) import qualified Data.Set as Set import qualified Data.Text as T import Data.Text (Text) +import System.FilePath (dropExtension) import Text.Pandoc.Class.PandocMonad (PandocMonad, report) import Text.Pandoc.Definition import Text.Pandoc.ImageSize @@ -152,10 +154,6 @@ blockToAsciiDoc opts (Div (id',"section":_,_) blockToAsciiDoc opts (Plain inlines) = do contents <- inlineListToAsciiDoc opts inlines return $ contents <> blankline -blockToAsciiDoc opts (SimpleFigure attr alternate (src, tit)) - -- image::images/logo.png[Company logo, title="blah"] - = (\args -> "image::" <> args <> blankline) <$> - imageArguments opts attr alternate src tit blockToAsciiDoc opts (Para inlines) = do contents <- inlineListToAsciiDoc opts inlines -- escape if para starts with ordered list marker @@ -189,7 +187,23 @@ blockToAsciiDoc opts (Header level (ident,_,_) inlines) = do return $ identifier $$ nowrap (text (replicate (level + 1) '=') <> space <> contents) <> blankline - +blockToAsciiDoc opts (Figure attr (Caption _ longcapt) body) = do + -- Images in figures all get rendered as individual block-level images + -- with the given caption. Non-image elements are rendered unchanged. + capt <- inlineListToAsciiDoc opts (blocksToInlines longcapt) + let renderFigElement = \case + Plain [Image imgAttr alternate (src, tit)] -> do + args <- imageArguments opts imgAttr alternate src tit + let figAttributes = case attr of + ("", _, _) -> empty + (ident, _, _) -> literal $ "[#" <> ident <> "]" + -- .Figure caption + -- image::images/logo.png[Company logo, title="blah"] + return $ "." <> nowrap capt $$ + figAttributes $$ + "image::" <> args <> blankline + blk -> blockToAsciiDoc opts blk + vcat <$> mapM renderFigElement body blockToAsciiDoc _ (CodeBlock (_,classes,_) str) = return $ flush ( if null classes then "...." $$ literal str $$ "...." @@ -615,7 +629,7 @@ imageArguments :: PandocMonad m => WriterOptions -> ADW m (Doc Text) imageArguments opts attr altText src title = do let txt = if null altText || (altText == [Str ""]) - then [Str "image"] + then [Str . T.pack . dropExtension $ T.unpack src] else altText linktext <- inlineListToAsciiDoc opts txt let linktitle = if T.null title diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index 858ad8761..b5543b036 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -21,6 +21,7 @@ import Data.Char (ord, isDigit) import Data.List (intersperse) import Data.List.NonEmpty (NonEmpty ((:|))) import Data.Maybe (isNothing, mapMaybe, catMaybes) +import Data.Monoid (Any (Any, getAny)) import Data.Text (Text) import qualified Data.Text as T import Network.URI (unEscapeString) @@ -186,14 +187,6 @@ blockToConTeXt (Div attr@(_,"section":_,_) innerContents <- blockListToConTeXt xs return $ header' $$ innerContents $$ footer' blockToConTeXt (Plain lst) = inlineListToConTeXt lst -blockToConTeXt (SimpleFigure attr txt (src, _)) = do - capt <- inlineListToConTeXt txt - img <- inlineToConTeXt (Image attr txt (src, "")) - let (ident, _, _) = attr - label = if T.null ident - then empty - else "[]" <> brackets (literal $ toLabel ident) - return $ blankline $$ "\\placefigure" <> label <> braces capt <> img <> blankline blockToConTeXt (Para lst) = do contents <- inlineListToConTeXt lst return $ contents <> blankline @@ -293,6 +286,24 @@ blockToConTeXt (Header level attr lst) = sectionHeader attr level lst NonSectionHeading blockToConTeXt (Table attr caption colspecs thead tbody tfoot) = tableToConTeXt (Ann.toTable attr caption colspecs thead tbody tfoot) +blockToConTeXt (Figure (ident, _, _) (Caption cshort clong) body) = do + title <- inlineListToConTeXt (blocksToInlines clong) + list <- maybe (pure empty) inlineListToConTeXt cshort + content <- blockListToConTeXt body + + let options = + ["reference=" <> literal (toLabel ident) | not (T.null ident)] + ++ ["title=" <> braces title | not (isEmpty title)] + ++ ["list=" <> braces list | not (isEmpty list)] + let hasSubfigures = getAny $ + query (Any . \case {Figure {} -> True; _ -> False}) body + return + $ "\\startplacefigure" <> brackets (mconcat $ intersperse "," options) + $$ (if hasSubfigures then "\\startfloatcombination" else empty) + $$ content + $$ (if hasSubfigures then "\\stopfloatcombination" else empty) + $$ "\\stopplacefigure" + $$ blankline tableToConTeXt :: PandocMonad m => Ann.Table -> WM m (Doc Text) tableToConTeXt (Ann.Table attr caption colspecs thead tbodies tfoot) = do diff --git a/src/Text/Pandoc/Writers/DocBook.hs b/src/Text/Pandoc/Writers/DocBook.hs index e9eceb60c..3f6d3cfda 100644 --- a/src/Text/Pandoc/Writers/DocBook.hs +++ b/src/Text/Pandoc/Writers/DocBook.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} {- | @@ -15,7 +16,7 @@ module Text.Pandoc.Writers.DocBook ( writeDocBook4, writeDocBook5 ) where import Control.Monad.Reader import Data.Generics (everywhere, mkT) import Data.Maybe (isNothing, maybeToList) -import Data.Monoid (Any (..)) +import Data.Monoid (All (..), Any (..)) import Data.Text (Text) import qualified Data.Text as T import qualified Text.Pandoc.Builder as B @@ -192,7 +193,7 @@ blockToDocBook opts (Div (id',"section":_,_) (Header lvl (_,classes,attrs) ils : -- Populate miscAttr with Header.Attr.attributes, filtering out non-valid DocBook section attributes, id, and xml:id -- Also enrich the role attribute with certain class tokens - miscAttr = enrichRole (filter (isSectionAttr version) attrs) classes + miscAttr = enrichRole (filter (isSectionAttr version) attrs) classes attribs = nsAttr <> idAttr <> miscAttr title' <- inlinesToDocBook opts ils contents <- blocksToDocBook opts bs @@ -234,18 +235,6 @@ blockToDocBook _ h@Header{} = do report $ BlockNotRendered h return empty blockToDocBook opts (Plain lst) = inlinesToDocBook opts lst --- title beginning with fig: indicates that the image is a figure -blockToDocBook opts (SimpleFigure attr txt (src, _)) = do - alt <- inlinesToDocBook opts txt - let capt = if null txt - then empty - else inTagsSimple "title" alt - return $ inTagsIndented "figure" $ - capt $$ - inTagsIndented "mediaobject" ( - inTagsIndented "imageobject" - (imageToDocBook opts attr src) $$ - inTagsSimple "textobject" (inTagsSimple "phrase" alt)) blockToDocBook opts (Para lst) | hasLineBreaks lst = flush . nowrap . inTagsSimple "literallayout" <$> inlinesToDocBook opts lst @@ -324,6 +313,36 @@ 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 capt@(Caption _ caption) body) = do + -- TODO: probably better to handle nested figures as mediaobject + let isAcceptable = \case + Table {} -> All False + Figure {} -> All False + _ -> All True + if not . getAll $ query isAcceptable body + -- Fallback to a div if the content cannot be included in a figure + then blockToDocBook opts $ figureDiv attr capt body + else do + title <- inlinesToDocBook opts (blocksToInlines caption) + let toMediaobject = \case + Plain [Image imgAttr inlns (src, _)] -> do + alt <- inlinesToDocBook opts inlns + pure $ inTagsIndented "mediaobject" ( + inTagsIndented "imageobject" + (imageToDocBook opts imgAttr src) $$ + if isEmpty alt + then empty + else inTagsSimple "textobject" (inTagsSimple "phrase" alt)) + _ -> ask >>= \case + DocBook4 -> pure mempty -- docbook4 requires media + DocBook5 -> blocksToDocBook opts body + mediaobjects <- mapM toMediaobject body + return $ + if isEmpty $ mconcat mediaobjects + then mempty -- figures must have at least some content + else inTagsIndented "figure" $ + inTagsSimple "title" title $$ + mconcat mediaobjects 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 1f69d2fa9..8970d75b8 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -5,6 +5,7 @@ {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE TypeApplications #-} {- | Module : Text.Pandoc.Writers.Docx Copyright : Copyright (C) 2012-2023 John MacFarlane @@ -63,7 +64,7 @@ import Text.Pandoc.Logging import Text.Pandoc.MIME (extensionFromMimeType, getMimeType, getMimeTypeDef) import Text.Pandoc.Options import Text.Pandoc.Writers.Docx.StyleMap -import Text.Pandoc.Writers.Docx.Table +import Text.Pandoc.Writers.Docx.Table as Table import Text.Pandoc.Writers.Docx.Types import Text.Pandoc.Shared import Text.Pandoc.Walk @@ -890,38 +891,6 @@ blockToOpenXML' opts (Plain lst) = do if isInTable || isInList then withParaProp prop block else block --- title beginning with fig: indicates that the image is a figure -blockToOpenXML' opts (SimpleFigure attr@(imgident, _, _) alt (src, tit)) = do - setFirstPara - fignum <- gets stNextFigureNum - unless (null alt) $ modify $ \st -> st{ stNextFigureNum = fignum + 1 } - let refid = if T.null imgident - then "ref_fig" <> tshow fignum - else "ref_" <> imgident - figname <- translateTerm Term.Figure - prop <- pStyleM $ - if null alt - then "Figure" - else "Captioned Figure" - paraProps <- local (\env -> env { envParaProperties = EnvProps (Just prop) [] <> envParaProperties env }) (getParaProps False) - contents <- inlinesToOpenXML opts [Image attr alt (src,tit)] - captionNode <- if null alt - then return [] - else withParaPropM (pStyleM "Image Caption") - $ blockToOpenXML opts - $ Para - $ if isEnabled Ext_native_numbering opts - then Span (refid,[],[]) - [Str (figname <> "\160"), - RawInline (Format "openxml") - ("<w:fldSimple w:instr=\"SEQ Figure" - <> " \\* ARABIC \"><w:r><w:t>" - <> tshow fignum - <> "</w:t></w:r></w:fldSimple>")] : Str ": " : alt - else alt - return $ - Elem (mknode "w:p" [] (map Elem paraProps ++ contents)) - : captionNode blockToOpenXML' opts (Para lst) | null lst && not (isEnabled Ext_empty_paragraphs opts) = return [] | otherwise = do @@ -990,6 +959,99 @@ blockToOpenXML' opts (DefinitionList items) = do l <- concat `fmap` mapM (definitionListItemToOpenXML opts) items setFirstPara return l +blockToOpenXML' opts (Figure (ident, _, _) (Caption _ longcapt) body) = do + setFirstPara + fignum <- gets stNextFigureNum + unless (null longcapt) $ modify $ \st -> st{ stNextFigureNum = fignum + 1 } + let refid = if T.null ident + then "ref_fig" <> tshow fignum + else "ref_" <> ident + figname <- translateTerm Term.Figure + prop <- pStyleM $ + if null longcapt + then "Figure" + else "Captioned Figure" + paraProps <- local + (\env -> env { envParaProperties = EnvProps (Just prop) [] <> + envParaProperties env }) + (getParaProps False) + + -- Figure contents + let simpleImage x = do + imgXML <- inlineToOpenXML opts x + pure $ Elem (mknode "w:p" [] (map Elem paraProps ++ imgXML)) + contentsNode <- case body of + [Plain [img@Image {}]] -> simpleImage img + [Para [img@Image {}]] -> simpleImage img + _ -> toFigureTable opts body + -- Caption + let imageCaption = withParaPropM (pStyleM "Image Caption") + . blocksToOpenXML opts + let fstCaptionPara inlns = Para $ + if not $ isEnabled Ext_native_numbering opts + then inlns + else let rawfld = RawInline (Format "openxml") $ mconcat + [ "<w:fldSimple w:instr=\"SEQ Figure" + , " \\* ARABIC \"><w:r><w:t>" + , tshow fignum + , "</w:t></w:r></w:fldSimple>" + ] + in Span (refid,[],[]) [Str (figname <> "\160") , rawfld] + : Str ": " : inlns + captionNode <- case longcapt of + [] -> return [] + (Para xs : bs) -> imageCaption (fstCaptionPara xs : bs) + (Plain xs : bs) -> imageCaption (fstCaptionPara xs : bs) + _ -> imageCaption longcapt + return $ contentsNode : captionNode + +toFigureTable :: PandocMonad m + => WriterOptions -> [Block] -> WS m Content +toFigureTable opts blks = do + modify $ \s -> s { stInTable = True } + let ncols = length blks + let textwidth = 7920 -- 5.5 in in twips (1 twip == 1/20 pt) + let cellfrac = 1 / fromIntegral ncols + let colwidth = tshow @Integer $ floor (textwidth * cellfrac) -- twips + let gridCols = replicate ncols $ mknode "w:gridCol" [("w:w", colwidth)] () + let scaleImage = \case + Image attr@(ident, classes, attribs) alt tgt -> + let dimWidth = case dimension Width attr of + Nothing -> Percent (cellfrac * 100) + Just d -> scaleDimension cellfrac d + dimHeight = scaleDimension cellfrac <$> dimension Height attr + attribs' = (tshow Width, tshow dimWidth) : + (case dimHeight of + Nothing -> id + Just h -> ((tshow Height, tshow h) :)) + [ (k, v) | (k, v) <- attribs + , k `notElem` ["width", "height"] + ] + in Image (ident, classes, attribs') alt tgt + x -> x + let blockToCell = Table.OOXMLCell nullAttr AlignCenter 1 1 . (:[]) + . walk scaleImage + tblBody <- Table.rowToOpenXML (blocksToOpenXML opts) . + Table.OOXMLRow Table.BodyRow nullAttr $ + map blockToCell blks + let tbl = mknode "w:tbl" [] + ( mknode "w:tblPr" [] + ( mknode "w:tblStyle" [("w:val","FigureTable")] () : + mknode "w:tblW" [ ("w:type", "auto"), ("w:w", "0") ] () : + mknode "w:tblLook" [ ("w:firstRow", "0") + , ("w:lastRow", "0") + , ("w:firstColumn", "0") + , ("w:lastColumn", "0") + ] () : + mknode "w:jc" [("w:val","center")] () : + [] + ) + : mknode "w:tblGrid" [] gridCols + : [tblBody] + ) + modify $ \s -> s { stInTable = False } + return $ Elem tbl + definitionListItemToOpenXML :: (PandocMonad m) => WriterOptions -> ([Inline],[[Block]]) diff --git a/src/Text/Pandoc/Writers/Docx/Table.hs b/src/Text/Pandoc/Writers/Docx/Table.hs index 5bce9d257..c8d3fc104 100644 --- a/src/Text/Pandoc/Writers/Docx/Table.hs +++ b/src/Text/Pandoc/Writers/Docx/Table.hs @@ -11,6 +11,10 @@ Conversion of table blocks to docx. -} module Text.Pandoc.Writers.Docx.Table ( tableToOpenXML + , rowToOpenXML + , OOXMLRow (..) + , OOXMLCell (..) + , RowType (..) ) where import Control.Monad.State.Strict ( modify, gets ) diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 66f44084b..e2b2a988c 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -36,7 +36,7 @@ import Text.Pandoc.ImageSize import Text.Pandoc.Logging import Text.Pandoc.Options (WrapOption (..), WriterOptions (writerTableOfContents, writerTemplate, writerWrapText)) -import Text.Pandoc.Shared (camelCaseToHyphenated, linesToPara, +import Text.Pandoc.Shared (camelCaseToHyphenated, figureDiv, linesToPara, removeFormatting, trimr, tshow) import Text.Pandoc.URI (escapeURI, isURI) import Text.Pandoc.Templates (renderTemplate) @@ -109,17 +109,6 @@ blockToDokuWiki opts (Div _attrs bs) = do blockToDokuWiki opts (Plain inlines) = inlineListToDokuWiki opts 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 (SimpleFigure attr txt (src, tit)) = do - capt <- if null txt - then return "" - else (" " <>) `fmap` inlineListToDokuWiki opts txt - let opt = if null txt - then "" - else "|" <> if T.null tit then capt else tit <> capt - return $ "{{" <> src <> imageDims opts attr <> opt <> "}}\n" - blockToDokuWiki opts (Para inlines) = do indent <- asks stIndent useTags <- asks stUseTags @@ -223,6 +212,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 attr capt body) = + blockToDokuWiki opts $ figureDiv attr capt 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 3d9770f53..e2d9deffe 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -37,8 +37,9 @@ import Text.Pandoc.Definition import Text.Pandoc.Error (PandocError(..)) import Text.Pandoc.Logging import Text.Pandoc.Options (HTMLMathMethod (..), WriterOptions (..), def) -import Text.Pandoc.Shared (capitalize, orderedListMarkers, +import Text.Pandoc.Shared (blocksToInlines, capitalize, orderedListMarkers, makeSections, tshow, stringify) +import Text.Pandoc.Walk (walk) import Text.Pandoc.Writers.Shared (lookupMetaString, toLegacyTable, ensureValidXmlIdentifiers) import Data.Generics (everywhere, mkT) @@ -299,11 +300,11 @@ mkitem mrk bs = do -- | Convert a block-level Pandoc's element to FictionBook XML representation. blockToXml :: PandocMonad m => Block -> FBM m [Content] +blockToXml (Plain [img@Image {}]) = insertImage NormalImage img blockToXml (Plain ss) = cMapM toXml ss -- FIXME: can lead to malformed FB2 +-- Special handling for singular images and display math elements blockToXml (Para [Math DisplayMath formula]) = insertMath NormalImage formula --- title beginning with fig: indicates that the image is a figure -blockToXml (SimpleFigure atr alt (src, tit)) = - insertImage NormalImage (Image atr alt (src,tit)) +blockToXml (Para [img@(Image {})]) = insertImage NormalImage img blockToXml (Para ss) = list . el "p" <$> cMapM toXml ss blockToXml (CodeBlock _ s) = return . spaceBeforeAfter . map (el "p" . el "code") . T.lines $ s @@ -361,6 +362,11 @@ blockToXml (Table _ blkCapt specs thead tbody tfoot) = do align_str AlignRight = "right" align_str AlignDefault = "left" blockToXml Null = return [] +blockToXml (Figure _attr (Caption _ longcapt) body) = + let alt = blocksToInlines longcapt + addAlt (Image imgattr [] tgt) = Image imgattr alt tgt + addAlt inln = inln + in cMapM blockToXml (walk addAlt 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 6ccb33bc8..4a1934387 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -1,5 +1,6 @@ -{-# LANGUAGE LambdaCase #-} {-# LANGUAGE BangPatterns #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE LambdaCase #-} {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} @@ -704,34 +705,6 @@ dimensionsToAttrList attr = go Width ++ go Height (Just x) -> [("style", tshow dir <> ":" <> tshow x)] Nothing -> [] -figure :: PandocMonad m - => WriterOptions -> Attr -> [Inline] -> (Text, Text) - -> StateT WriterState m Html -figure opts attr@(_, _, attrList) txt (s,tit) = do - html5 <- gets stHtml5 - -- Screen-readers will normally read the @alt@ text and the figure; we - -- want to avoid them reading the same text twice. With HTML5 we can - -- use aria-hidden for the caption; with HTML4, we use an empty - -- alt-text instead. - -- When the alt text differs from the caption both should be read. - let alt = if html5 then txt else [Str ""] - let tocapt = if html5 - then (H5.figcaption !) $ - if isJust (lookup "alt" attrList) - then mempty - else H5.customAttribute (textTag "aria-hidden") - (toValue @Text "true") - else H.p ! A.class_ "caption" - img <- inlineToHtml opts (Image attr alt (s,tit)) - capt <- if null txt - then return mempty - else (nl <>) . tocapt <$> inlineListToHtml opts txt - let inner = mconcat [nl, img, capt, nl] - return $ if html5 - then H5.figure inner - else H.div ! A.class_ "figure" $ inner - - adjustNumbers :: WriterOptions -> [Block] -> [Block] adjustNumbers opts doc = if all (==0) (writerNumberOffset opts) @@ -754,23 +727,19 @@ adjustNumbers opts doc = blockToHtmlInner :: PandocMonad m => WriterOptions -> Block -> StateT WriterState m Html blockToHtmlInner _ Null = return mempty blockToHtmlInner opts (Plain lst) = inlineListToHtml opts lst -blockToHtmlInner opts (Para [Image attr@(_,classes,_) txt (src,tit)]) - | "r-stretch" `elem` classes = do - slideVariant <- gets stSlideVariant - case slideVariant of - RevealJsSlides -> - -- a "stretched" image in reveal.js must be a direct child - -- 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 (SimpleFigure attr caption (src, title)) = - figure opts attr caption (src, title) blockToHtmlInner opts (Para lst) = do - contents <- inlineListToHtml opts lst - case contents of - Empty _ | not (isEnabled Ext_empty_paragraphs opts) -> return mempty - _ -> return $ H.p contents + slideVariant <- gets stSlideVariant + case (slideVariant, lst) of + (RevealJsSlides, [Image attr@(_,classes,_) txt (src,tit)]) + | "r-stretch" `elem` classes -> do + -- a "stretched" image in reveal.js must be a direct child + -- of the slide container + inlineToHtml opts (Image attr txt (src, tit)) + _ -> do + contents <- inlineListToHtml opts lst + case contents of + Empty _ | not (isEnabled Ext_empty_paragraphs opts) -> return mempty + _ -> return $ H.p contents blockToHtmlInner opts (LineBlock lns) = if writerWrapText opts == WrapNone then blockToHtml opts $ linesToPara lns @@ -1050,6 +1019,34 @@ 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) +blockToHtmlInner opts (Figure attrs (Caption _ captBody) body) = do + html5 <- gets stHtml5 + + figAttrs <- attrsToHtml opts attrs + contents <- blockListToHtml opts body + figCaption <- if null captBody + then return mempty + else do + captCont <- blockListToHtml opts captBody + return . mconcat $ + if html5 + then let fcattr = if captionIsAlt captBody body + then H5.customAttribute + (textTag "aria-hidden") + (toValue @Text "true") + else mempty + in [ H5.figcaption ! fcattr $ captCont, nl ] + else [ (H.div ! A.class_ "figcaption") captCont, nl ] + return $ + if html5 + then foldl (!) H5.figure figAttrs $ mconcat [nl, contents, nl, figCaption] + else foldl (!) H.div (A.class_ "float" : figAttrs) $ mconcat + [nl, contents, nl, figCaption] + where + captionIsAlt capt [Plain [Image (_, _, kv) desc _]] = + let alt = fromMaybe (stringify desc) $ lookup "alt" kv + in stringify capt == alt + captionIsAlt _ _ = False -- | 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 6f8594ff5..c2bcddf83 100644 --- a/src/Text/Pandoc/Writers/Haddock.hs +++ b/src/Text/Pandoc/Writers/Haddock.hs @@ -100,9 +100,6 @@ blockToHaddock opts (Div _ ils) = do blockToHaddock opts (Plain inlines) = do contents <- inlineListToHaddock opts inlines return $ contents <> cr --- title beginning with fig: indicates figure -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 (<> blankline) `fmap` blockToHaddock opts (Plain inlines) @@ -152,6 +149,9 @@ blockToHaddock opts (OrderedList (start,_,delim) items) = do blockToHaddock opts (DefinitionList items) = do contents <- mapM (definitionListItemToHaddock opts) items return $ vcat contents <> blankline +blockToHaddock opts (Figure _ (Caption _ longcapt) body) = + -- Haddock has no concept of figures, floats, or captions. + fmap (<> blankline) (blockListToHaddock opts (body ++ longcapt)) -- | 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 7c39a99c4..5f660bc2d 100644 --- a/src/Text/Pandoc/Writers/ICML.hs +++ b/src/Text/Pandoc/Writers/ICML.hs @@ -312,10 +312,6 @@ 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 -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 blockToICML opts style (LineBlock lns) = blockToICML opts style $ linesToPara lns @@ -387,6 +383,16 @@ 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 capt@(Caption _ longcapt) body) = + case body of + [Plain [img@(Image {})]] -> do + figure <- parStyle opts (figureName:style) "" [img] + caption <- parStyle opts (imgCaptionName:style) "" $ + blocksToInlines longcapt + return $ intersperseBrs [figure, caption] + _ -> -- fallback to rendering the figure as a Div + blockToICML opts style $ figureDiv attr capt 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 16a7fb672..f19be1445 100644 --- a/src/Text/Pandoc/Writers/JATS.hs +++ b/src/Text/Pandoc/Writers/JATS.hs @@ -220,17 +220,6 @@ listItemToJATS opts mbmarker item = do maybe empty (inTagsSimple "label" . text . T.unpack) mbmarker $$ contents -imageMimeType :: Text -> [(Text, Text)] -> (Text, Text) -imageMimeType src kvs = - let mbMT = getMimeType (T.unpack src) - maintype = fromMaybe "image" $ - lookup "mimetype" kvs `mplus` - (T.takeWhile (/='/') <$> mbMT) - subtype = fromMaybe "" $ - lookup "mime-subtype" kvs `mplus` - (T.drop 1 . T.dropWhile (/='/') <$> mbMT) - in (maintype, subtype) - languageFor :: WriterOptions -> [Text] -> Text languageFor opts classes = case langs of @@ -301,35 +290,13 @@ blockToJATS opts (Div (ident,_,kvs) bs) = do blockToJATS opts (Header _ _ title) = do title' <- inlinesToJATS opts (map fixLineBreak title) return $ inTagsSimple "title" title' +-- Special cases for bare images, which are rendered as graphics +blockToJATS _opts (Plain [Image attr alt tgt]) = + return $ graphic attr alt tgt +blockToJATS _opts (Para [Image attr alt tgt]) = + return $ graphic attr alt tgt -- No Plain, everything needs to be in a block-level tag blockToJATS opts (Plain lst) = blockToJATS opts (Para lst) -blockToJATS opts (SimpleFigure (ident, _, kvs) txt (src, tit)) = do - alt <- inlinesToJATS opts txt - let (maintype, subtype) = imageMimeType src kvs - let capt = if null txt - then empty - else inTagsSimple "caption" $ inTagsSimple "p" alt - let attr = [("id", escapeNCName ident) | not (T.null ident)] ++ - [(k,v) | (k,v) <- kvs, k `elem` ["fig-type", "orientation", - "position", "specific-use"]] - let graphicattr = [("mimetype",maintype), - ("mime-subtype",subtype), - ("xlink:href",src), -- do we need to URL escape this? - ("xlink:title",tit)] - return $ inTags True "fig" attr $ - capt $$ selfClosingTag "graphic" graphicattr -blockToJATS _ (Para [Image (ident,_,kvs) _ (src, tit)]) = do - let (maintype, subtype) = imageMimeType src kvs - let attr = [("id", escapeNCName ident) | not (T.null ident)] ++ - [("mimetype", maintype), - ("mime-subtype", subtype), - ("xlink:href", src)] ++ - [("xlink:title", tit) | not (T.null tit)] ++ - [(k,v) | (k,v) <- kvs, k `elem` ["baseline-shift", - "content-type", "specific-use", "xlink:actuate", - "xlink:href", "xlink:role", "xlink:show", - "xlink:type"]] - return $ selfClosingTag "graphic" attr blockToJATS opts (Para lst) = inTagsSimple "p" <$> inlinesToJATS opts lst blockToJATS opts (LineBlock lns) = @@ -385,6 +352,16 @@ 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 (ident, _, kvs) caption body) = do + capt <- case caption of + Caption _ [] -> pure empty + Caption _ cpt -> inTagsSimple "caption" <$> blocksToJATS opts cpt + figbod <- blocksToJATS opts body + let figattr = [("id", escapeNCName ident) | not (T.null ident)] ++ + [(k,v) | (k,v) <- kvs + , k `elem` [ "fig-type", "orientation" + , "position", "specific-use"]] + return $ inTags True "fig" figattr $ capt $$ figbod -- | Convert a list of inline elements to JATS. inlinesToJATS :: PandocMonad m => WriterOptions -> [Inline] -> JATS m (Doc Text) @@ -543,27 +520,40 @@ inlineToJATS opts (Link (ident,_,kvs) txt (src, tit)) = do "xlink:type"]] contents <- inlinesToJATS opts txt return $ inTags False "ext-link" attr contents -inlineToJATS _ (Image (ident,_,kvs) _ (src, tit)) = do +inlineToJATS _ (Image attr alt tgt) = do + return $ selfClosingTag "inline-graphic" (graphicAttr attr alt tgt) + +graphic :: Attr -> [Inline] -> Target -> (Doc Text) +graphic attr alt tgt = + selfClosingTag "graphic" (graphicAttr attr alt tgt) + +graphicAttr :: Attr -> [Inline] -> Target -> [(Text, Text)] +graphicAttr (ident, _, kvs) _alt (src, tit) = + let (maintype, subtype) = imageMimeType src kvs + in [("id", escapeNCName ident) | not (T.null ident)] ++ + [ ("mimetype", maintype) + , ("mime-subtype", subtype) + , ("xlink:href", src) + ] ++ + [("xlink:title", tit) | not (T.null tit)] ++ + [(k,v) | (k,v) <- kvs + , k `elem` [ "baseline-shift", "content-type", "specific-use" + , "xlink:actuate", "xlink:href", "xlink:role" + , "xlink:show", "xlink:type"] + ] + +imageMimeType :: Text -> [(Text, Text)] -> (Text, Text) +imageMimeType src kvs = let mbMT = getMimeType (T.unpack src) - let maintype = fromMaybe "image" $ + maintype = fromMaybe "image" $ lookup "mimetype" kvs `mplus` (T.takeWhile (/='/') <$> mbMT) - let subtype = fromMaybe "" $ + subtype = fromMaybe "" $ lookup "mime-subtype" kvs `mplus` (T.drop 1 . T.dropWhile (/='/') <$> mbMT) - let attr = [("id", escapeNCName ident) | not (T.null ident)] ++ - [("mimetype", maintype), - ("mime-subtype", subtype), - ("xlink:href", src)] ++ - [("xlink:title", tit) | not (T.null tit)] ++ - [(k,v) | (k,v) <- kvs, k `elem` ["baseline-shift", - "content-type", "specific-use", "xlink:actuate", - "xlink:href", "xlink:role", "xlink:show", - "xlink:type"]] - return $ selfClosingTag "inline-graphic" attr + in (maintype, subtype) isParaOrList :: Block -> Bool -isParaOrList SimpleFigure{} = False -- implicit figures are not paragraphs isParaOrList Para{} = True isParaOrList Plain{} = True isParaOrList BulletList{} = True diff --git a/src/Text/Pandoc/Writers/Jira.hs b/src/Text/Pandoc/Writers/Jira.hs index 612e517c7..7b637268b 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 0585a7111..6dd259dae 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -3,6 +3,7 @@ {-# LANGUAGE TupleSections #-} {-# LANGUAGE PatternGuards #-} {-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeApplications #-} {-# LANGUAGE ViewPatterns #-} {- | Module : Text.Pandoc.Writers.LaTeX @@ -33,6 +34,7 @@ import Data.Containers.ListUtils (nubOrd) import Data.Char (isDigit) import Data.List (intersperse, (\\)) import Data.Maybe (catMaybes, fromMaybe, isJust, mapMaybe, isNothing) +import Data.Monoid (Any (..)) import Data.Text (Text) import qualified Data.Text as T import Network.URI (unEscapeString) @@ -176,6 +178,7 @@ pandocToLaTeX options (Pandoc meta blocks) = do defField "numbersections" (writerNumberSections options) $ defField "lhs" (stLHS st) $ defField "graphics" (stGraphics st) $ + defField "subfigure" (stSubfigure st) $ defField "svg" (stSVG st) $ defField "has-chapters" (stHasChapters st) $ defField "has-frontmatter" (documentClass `elem` frontmatterClasses) $ @@ -366,21 +369,6 @@ blockToLaTeX (Div (identifier,classes,kvs) bs) = do wrapNotes <$> wrapDiv (identifier,classes,kvs) result blockToLaTeX (Plain lst) = inlineListToLaTeX lst -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 - img <- inlineToLaTeX (Image attr txt (src,tit)) - innards <- hypertarget True ident $ - "\\centering" $$ img $$ caption <> cr - let figure = cr <> "\\begin{figure}" $$ innards $$ "\\end{figure}" - st <- get - return $ (if stInMinipage st - -- can't have figures in notes or minipage (here, table cell) - -- http://www.tex.ac.uk/FAQ-ouparmd.html - then cr <> "\\begin{center}" $$ img $+$ capt $$ - "\\end{center}" - else figure) $$ footnotes -- . . . indicates pause in beamer slides blockToLaTeX (Para [Str ".",Space,Str ".",Space,Str "."]) = do beamer <- gets stBeamer @@ -576,6 +564,58 @@ 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 (ident, _, _) (Caption _ longCapt) body) = do + (capt, captForLof, footnotes) <- getCaption inlineListToLaTeX True + (blocksToInlines longCapt) + lab <- labelFor ident + let caption = "\\caption" <> captForLof <> braces capt <> lab + + isSubfigure <- gets stInFigure + modify $ \st -> st{ stInFigure = True } + contents <- case body of + [b] -> blockToLaTeX b + bs -> mconcat . intersperse (cr <> "\\hfill") <$> + mapM (toSubfigure (length bs)) bs + innards <- hypertarget True ident $ + "\\centering" $$ contents $$ caption <> cr + modify $ \st -> + st{ stInFigure = isSubfigure + , stSubfigure = stSubfigure st || isSubfigure + } + + let containsTable = getAny . (query $ \case + Table {} -> Any True + _ -> Any False) + st <- get + return $ (case () of + _ | containsTable body -> + -- placing a longtable in a figure or center environment does + -- not make sense. + cr <> contents + _ | stInMinipage st -> + -- can't have figures in notes or minipage (here, table cell) + -- http://www.tex.ac.uk/FAQ-ouparmd.html + cr <> "\\begin{center}" $$ contents $+$ capt $$ "\\end{center}" + _ | isSubfigure -> + innards + _ -> cr <> "\\begin{figure}" $$ innards $$ "\\end{figure}") + $$ footnotes + +toSubfigure :: PandocMonad m => Int -> Block -> LW m (Doc Text) +toSubfigure nsubfigs blk = do + contents <- blockToLaTeX blk + let linewidth = tshow @Double (0.9 / fromIntegral nsubfigs) <> "\\linewidth" + return $ cr <> case blk of + Figure {} -> vcat + [ "\\begin{subfigure}[t]" <> braces (literal linewidth) + , contents + , "\\end{subfigure}" + ] + _ -> vcat + [ "\\begin{minipage}[t]" <> braces (literal linewidth) + , contents + , "\\end{minipage}" + ] blockListToLaTeX :: PandocMonad m => [Block] -> LW m (Doc Text) blockListToLaTeX lst = diff --git a/src/Text/Pandoc/Writers/LaTeX/Types.hs b/src/Text/Pandoc/Writers/LaTeX/Types.hs index ff5b22cad..97ac1dcf9 100644 --- a/src/Text/Pandoc/Writers/LaTeX/Types.hs +++ b/src/Text/Pandoc/Writers/LaTeX/Types.hs @@ -25,12 +25,14 @@ data WriterState = , stInMinipage :: Bool -- ^ true if in minipage , stInHeading :: Bool -- ^ true if in a section heading , stInItem :: Bool -- ^ true if in \item[..] + , stInFigure :: Bool -- ^ true if in figure environment , stNotes :: [Doc Text] -- ^ notes in a minipage , stOLLevel :: Int -- ^ level of ordered list nesting , stOptions :: WriterOptions -- ^ writer options, so they don't have to -- be parameter , stVerbInNote :: Bool -- ^ true if document has verbatim text in note , stTable :: Bool -- ^ true if document has a table + , stSubfigure :: Bool -- ^ true if document has subfigures , stMultiRow :: Bool -- ^ true if document has multirow cells , stStrikeout :: Bool -- ^ true if document has strikeout , stUrl :: Bool -- ^ true if document has visible URL link @@ -58,11 +60,13 @@ startingState options = , stInHeading = False , stInMinipage = False , stInItem = False + , stInFigure = False , stNotes = [] , stOLLevel = 1 , stOptions = options , stVerbInNote = False , stTable = False + , stSubfigure = False , stMultiRow = False , stStrikeout = False , stUrl = False diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs index 5573a9838..1ea5b8650 100644 --- a/src/Text/Pandoc/Writers/Man.hs +++ b/src/Text/Pandoc/Writers/Man.hs @@ -173,7 +173,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) @@ -186,6 +185,8 @@ blockToMan opts (OrderedList attribs items) = do blockToMan opts (DefinitionList items) = do contents <- mapM (definitionListItemToMan opts) items return (vcat contents) +blockToMan opts (Figure attr capt body) = do + blockToMan opts (figureDiv attr capt 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 cde993091..95dedb0b5 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -25,7 +25,7 @@ import Control.Monad (foldM, zipWithM, MonadPlus(..), when) import Control.Monad.Reader ( asks, MonadReader(local) ) import Control.Monad.State.Strict ( gets, modify ) import Data.Default -import Data.List (intersperse, sortOn) +import Data.List (intersperse, sortOn, union) import Data.List.NonEmpty (nonEmpty, NonEmpty(..)) import qualified Data.Map as M import Data.Maybe (fromMaybe, mapMaybe, isNothing) @@ -427,14 +427,6 @@ blockToMarkdown' opts (Plain inlines) = do _ -> inlines contents <- inlineListToMarkdown opts inlines' return $ contents <> cr -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 [SimpleFigure attr alt (src, tit)]) - | otherwise = blockToMarkdown opts (Para [Image attr alt (src,tit)]) blockToMarkdown' opts (Para inlines) = (<> blankline) `fmap` blockToMarkdown opts (Plain inlines) blockToMarkdown' opts (LineBlock lns) = @@ -677,6 +669,33 @@ 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 figattr capt body) = do + let combinedAttr imgattr = case imgattr of + ("", cls, kv) | (figid, [], []) <- figattr -> Just (figid, cls, kv) + _ -> Nothing + let combinedAlt alt = case capt of + Caption Nothing [] -> if null alt + then Just [Str "image"] + else Just alt + Caption Nothing [Plain captInlines] + | captInlines == alt -> Just captInlines + _ -> Nothing + case body of + [Plain [Image imgAttr alt (src, ttl)]] + | isEnabled Ext_implicit_figures opts + , Just descr <- combinedAlt alt + , Just imgAttr' <- combinedAttr imgAttr + , isEnabled Ext_link_attributes opts || imgAttr' == nullAttr + -> do + -- use implicit figures if possible + let tgt' = (src, fromMaybe ttl $ T.stripPrefix "fig:" ttl) + contents <- inlineListToMarkdown opts [Image imgAttr' descr tgt'] + return $ contents <> blankline + _ -> + -- fallback to raw html if possible or div otherwise + if isEnabled Ext_raw_html opts + then figureToMarkdown opts figattr capt body + else blockToMarkdown' opts $ figureDiv figattr capt body inList :: Monad m => MD m a -> MD m a inList p = local (\env -> env {envInList = True}) p @@ -690,6 +709,22 @@ addMarkdownAttribute s = x /= "markdown"] _ -> s +-- | Converts a figure to Markdown by wrapping it in a div named `figure`. +figureToMarkdown :: PandocMonad m + => WriterOptions + -> Attr + -> Caption + -> [Block] + -> MD m (Doc Text) +figureToMarkdown opts attr@(ident, classes, kvs) capt body + | isEnabled Ext_raw_html opts = + (<> blankline) . literal . T.strip <$> + writeHtml5String + opts{ writerTemplate = Nothing } + (Pandoc nullMeta [Figure attr capt body]) + | otherwise = let attr' = (ident, ["figure"] `union` classes, kvs) + in blockToMarkdown' opts (Div attr' body) + itemEndsWithTightList :: [Block] -> Bool itemEndsWithTightList bs = case bs of diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index b93226d08..a244a52ff 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -16,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 @@ -202,6 +203,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 deea93f97..938ee881e 100644 --- a/src/Text/Pandoc/Writers/Ms.hs +++ b/src/Text/Pandoc/Writers/Ms.hs @@ -303,7 +303,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 @@ -319,6 +318,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 803394212..c254746b4 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -280,6 +280,8 @@ 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 attr capt body) = do + blockToMuse (figureDiv attr capt body) -- | 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 f7142b785..38a04341f 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -60,7 +60,7 @@ type OD m = StateT WriterState m data ReferenceType = HeaderRef | TableRef - | ImageRef + | FigureRef data WriterState = WriterState { stNotes :: [Doc Text] @@ -253,12 +253,11 @@ writeOpenDocument opts (Pandoc meta blocks) = do meta ((body, metadata),s) <- flip runStateT defaultWriterState $ do - let collectInlineIdent (Image (ident,_,_) _ _) = [(ident,ImageRef)] - collectInlineIdent _ = [] let collectBlockIdent (Header _ (ident,_,_) _) = [(ident,HeaderRef)] + collectBlockIdent (Figure (ident,_,_) _ _ ) = [(ident,FigureRef)] collectBlockIdent (Table (ident,_,_) _ _ _ _ _) = [(ident,TableRef)] collectBlockIdent _ = [] - modify $ \s -> s{ stIdentTypes = query collectBlockIdent blocks ++ query collectInlineIdent blocks } + modify $ \s -> s{ stIdentTypes = query collectBlockIdent blocks } m <- metaToContext opts (blocksToOpenDocument opts) (fmap chomp . inlinesToOpenDocument opts) @@ -377,7 +376,6 @@ blockToOpenDocument o = \case Plain b -> if null b then return empty else inParagraphTags =<< inlinesToOpenDocument o b - 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 +397,7 @@ blockToOpenDocument o = \case then return $ text $ T.unpack s else empty <$ report (BlockNotRendered b) Null -> return empty + Figure a capt b -> figure a capt b where defList b = do setInDefinitionList True r <- vcat <$> mapM (deflistItemToOpenDocument o) b @@ -454,15 +453,18 @@ blockToOpenDocument o = \case , ("table:style-name", name) ] (vcat columns $$ th $$ vcat tr) return $ captionDoc $$ tableDoc - figure attr@(ident, _, _) caption source title | null caption = - withParagraphStyle o "Figure" [Para [Image attr caption (source,title)]] - | otherwise = do - imageDoc <- withParagraphStyle o "FigureWithCaption" [Para [Image attr caption (source,title)]] - captionDoc <- inlinesToOpenDocument o caption >>= - if isEnabled Ext_native_numbering o - then numberedFigureCaption ident - else unNumberedCaption "FigureCaption" - return $ imageDoc $$ captionDoc + figure (ident, _, _) (Caption _ longcapt) body = + case blocksToInlines longcapt of + [] -> + withParagraphStyle o "Figure" body + caption -> do + imageDoc <- withParagraphStyle o "FigureWithCaption" $ + map (\case {Plain i -> Para i; b -> b}) body + captionDoc <- inlinesToOpenDocument o caption >>= + if isEnabled Ext_native_numbering o + then numberedFigureCaption ident + else unNumberedCaption "FigureCaption" + return $ imageDoc $$ captionDoc numberedTableCaption :: PandocMonad m => Text -> Doc Text -> OD m (Doc Text) @@ -705,7 +707,7 @@ mkLink o identTypes s t d = linkOrReference = case maybeIdentAndType of Just (ident, HeaderRef) -> bookmarkRef' ident Just (ident, TableRef) -> sequenceRef' ident - Just (ident, ImageRef) -> sequenceRef' ident + Just (ident, FigureRef) -> sequenceRef' ident _ -> link in if isEnabled Ext_xrefs_name o || isEnabled Ext_xrefs_number o then linkOrReference diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs index 751217e61..f8d16e924 100644 --- a/src/Text/Pandoc/Writers/Org.hs +++ b/src/Text/Pandoc/Writers/Org.hs @@ -123,12 +123,6 @@ blockToOrg (Div attr@(ident,_,_) bs) = do then return mempty else divToOrg attr bs blockToOrg (Plain inlines) = inlineListToOrg inlines -blockToOrg (SimpleFigure attr txt (src, tit)) = do - capt <- if null txt - then return empty - else ("#+caption: " <>) `fmap` inlineListToOrg txt - img <- inlineToOrg (Image attr txt (src,tit)) - return $ capt $$ img $$ blankline blockToOrg (Para inlines) = do contents <- inlineListToOrg inlines return $ contents <> blankline @@ -234,6 +228,18 @@ blockToOrg (OrderedList (start, _, delim) items) = do blockToOrg (DefinitionList items) = do contents <- mapM definitionListItemToOrg items return $ vcat contents $$ blankline +blockToOrg (Figure (ident, _, _) caption body) = do + -- Represent the figure as content that can be internally linked from other + -- parts of the document. + capt <- case caption of + Caption _ [] -> pure empty + Caption _ cpt -> ("#+caption: " <>) <$> + inlineListToOrg (blocksToInlines cpt) + contents <- blockListToOrg body + let anchor = if T.null ident + then empty + else "<<" <> literal ident <> ">>" + return (capt $$ anchor $$ 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 49f4f656f..520cf4826 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs @@ -537,6 +537,8 @@ blockToParagraphs (Div (_, classes, _) blks) = let | otherwise -> Nothing addIncremental env = env { envInIncrementalDiv = incremental } in local addIncremental (concatMapM blockToParagraphs blks) +blockToParagraphs (Figure attr capt blks) = + blockToParagraphs (Shared.figureDiv attr capt blks) blockToParagraphs blk = do addLogMessage $ BlockNotRendered blk return [] @@ -1041,6 +1043,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 4567b44df..d2ba258fe 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -263,20 +263,6 @@ blockToRST (Div (ident,classes,_kvs) bs) = do nest 3 contents $$ blankline blockToRST (Plain inlines) = inlineListToRST inlines -blockToRST (SimpleFigure attr txt (src, tit)) = do - description <- inlineListToRST txt - dims <- imageDimsToRST attr - 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 @@ -409,6 +395,36 @@ blockToRST (DefinitionList items) = do -- ensure that sublists have preceding blank line return $ blankline $$ vcat contents $$ blankline +blockToRST (Figure (ident, classes, _) _ body) = do + let figure attr txt (src, tit) = do + description <- inlineListToRST txt + dims <- imageDimsToRST attr + let fig = "figure:: " <> literal src + alt = ":alt: " <> if T.null tit then description else literal tit + capt = description + (_,cls,_) = attr + align = 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 $$ align $$ dims $+$ capt) + $$ blankline + case body of + [Para [Image attr txt tgt]] -> figure attr txt tgt + [Plain [Image attr txt tgt]] -> figure attr txt tgt + _ -> 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 diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index 2c012d85e..2f13627e6 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -270,6 +270,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 capt body) = + blockToRTF indent alignment $ figureDiv attr capt 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 6c7a5bb49..f0efa9952 100644 --- a/src/Text/Pandoc/Writers/TEI.hs +++ b/src/Text/Pandoc/Writers/TEI.hs @@ -130,18 +130,6 @@ blockToTEI _ h@Header{} = do -- we use treat as Para to ensure that Plain text ends up contained by -- something: blockToTEI opts (Plain lst) = blockToTEI opts $ Para lst --- title beginning with fig: indicates that the image is a figure ---blockToTEI opts (Para [Image attr txt (src,'f':'i':'g':':':_)]) = --- let alt = inlinesToTEI opts txt --- capt = if null txt --- then empty --- else inTagsSimple "title" alt --- in inTagsIndented "figure" $ --- capt $$ --- (inTagsIndented "mediaobject" $ --- (inTagsIndented "imageobject" --- (imageToTEI opts attr src)) $$ --- inTagsSimple "textobject" (inTagsSimple "phrase" alt)) blockToTEI opts (Para lst) = inTags False "p" [] <$> inlinesToTEI opts lst blockToTEI opts (LineBlock lns) = @@ -193,6 +181,8 @@ blockToTEI _ HorizontalRule = return $ selfClosingTag "milestone" [("unit","undefined") ,("type","separator") ,("rendition","line")] +blockToTEI opts (Figure attr capt bs) = + blockToTEI opts (figureDiv attr capt bs) -- 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 ed9c8e840..ca27a0a32 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -125,15 +125,6 @@ blockToTexinfo (Div _ bs) = blockListToTexinfo bs blockToTexinfo (Plain lst) = inlineListToTexinfo lst --- title beginning with fig: indicates that the image is a figure -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" - blockToTexinfo (Para lst) = inlineListToTexinfo lst -- this is handled differently from Plain in blockListToTexinfo @@ -257,11 +248,44 @@ 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 [SimpleFigure attr figCaption tgt]) = do + let capt = if null figCaption + then let (Caption _ cblks) = caption + in blocksToInlines cblks + else figCaption + captionText <- if null capt + then return empty + else (text "@caption" <>) . braces <$> inlineListToTexinfo capt + img <- inlineToTexinfo (Image attr figCaption tgt) + return $ text "@float Figure" $$ img $$ captionText $$ text "@end float" + +blockToTexinfo (Figure _ fCaption [ + Table attr tCaption@(Caption _ cbody) specs thead tbody tfoot]) = do + let caption = case cbody of + [] -> fCaption + _ -> tCaption + blockToTexinfo (Table attr caption 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 according to + -- https://www.gnu.org/software/texinfo/manual/texinfo/html_node/_0040float.html + 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 115756f1d..0f38d91e6 100644 --- a/src/Text/Pandoc/Writers/Textile.hs +++ b/src/Text/Pandoc/Writers/Textile.hs @@ -111,11 +111,6 @@ blockToTextile opts (Div attr bs) = do blockToTextile opts (Plain inlines) = inlineListToTextile opts inlines -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 - blockToTextile opts (Para inlines) = do useTags <- gets stUseTags listLevel <- gets stListLevel @@ -243,6 +238,19 @@ blockToTextile opts (DefinitionList items) = do contents <- withUseTags $ mapM (definitionListItemToTextile opts) items return $ "<dl>\n" <> vcat contents <> "\n</dl>\n" +blockToTextile opts (Figure attr (Caption _ caption) body) = do + let startTag = render Nothing $ tagWithAttrs "figure" attr + let endTag = "</figure>" + let captionInlines = blocksToInlines caption + captionMarkup <- if null captionInlines + then return "" + else ((<> "\n\n</figcaption>\n\n") . ("<figcaption>\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 f3389d0fd..87eda20ac 100644 --- a/src/Text/Pandoc/Writers/XWiki.hs +++ b/src/Text/Pandoc/Writers/XWiki.hs @@ -1,6 +1,6 @@ {-# LANGUAGE OverloadedStrings #-} {- -Copyright (C) 2008-2017 John MacFarlane <[email protected]> +Copyright (C) 2008-2023 John MacFarlane <[email protected]> This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.XWiki - Copyright : Copyright (C) 2008-2017 John MacFarlane + Copyright : Copyright (C) 2008-2023 John MacFarlane License : GNU GPL, version 2 or above Maintainer : Derek Chen-Becker <[email protected]> @@ -135,6 +135,12 @@ blockToXWiki (DefinitionList items) = do contents <- local (\s -> s { listLevel = listLevel s <> ";" }) $ mapM definitionListItemToMediaWiki items return $ vcat contents <> if Text.null lev then "\n" else "" +-- Create a group according to +-- https://www.xwiki.org/xwiki/bin/view/Documentation/UserGuide/Features/XWikiSyntax/?syntax=2.1§ion=Groups +blockToXWiki (Figure attr _ body) = do + content <- blockToXWiki $ Div attr body + return $ intercalate content ["(((\n", "\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 77d627ed1..6e8f49ed9 100644 --- a/src/Text/Pandoc/Writers/ZimWiki.hs +++ b/src/Text/Pandoc/Writers/ZimWiki.hs @@ -32,7 +32,7 @@ import Text.Pandoc.Logging import Text.Pandoc.Options (WrapOption (..), WriterOptions (writerTableOfContents, writerTemplate, writerWrapText)) -import Text.Pandoc.Shared (linesToPara, removeFormatting, trimr) +import Text.Pandoc.Shared (figureDiv, linesToPara, removeFormatting, trimr) import Text.Pandoc.URI (escapeURI, isURI) import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Writers.Shared (defField, metaToContext, toLegacyTable) @@ -86,16 +86,6 @@ blockToZimWiki opts (Div _attrs bs) = do blockToZimWiki opts (Plain inlines) = inlineListToZimWiki opts inlines --- ZimWiki doesn't support captions - so combine together alt and caption into alt -blockToZimWiki opts (SimpleFigure attr txt (src, tit)) = do - capt <- if null txt - then return "" - else (" " <>) `fmap` inlineListToZimWiki opts txt - let opt = if null txt - then "" - else "|" <> if T.null tit then capt else tit <> capt - return $ "{{" <> src <> imageDims opts attr <> opt <> "}}\n" - blockToZimWiki opts (Para inlines) = do indent <- gets stIndent -- useTags <- gets stUseTags @@ -180,6 +170,9 @@ blockToZimWiki opts (DefinitionList items) = do contents <- mapM (definitionListItemToZimWiki opts) items return $ vcat contents +blockToZimWiki opts (Figure attr capt body) = do + blockToZimWiki opts (figureDiv attr capt body) + definitionListItemToZimWiki :: PandocMonad m => WriterOptions -> ([Inline],[[Block]]) diff --git a/stack.yaml b/stack.yaml index 3c90a2e40..f7a7bfc24 100644 --- a/stack.yaml +++ b/stack.yaml @@ -28,7 +28,10 @@ extra-deps: commit: 1a77db688bd3285228299e5aeefc93d6c0d8c0b9 - git: https://github.com/jgm/citeproc commit: 4099185c5a82ef1f84b711c113d2744eeb794106 - +- git: https://github.com/tarleb/pandoc-types + commit: f84b7359765a2798f22efe4e9457538cda7a8d4a +- git: https://github.com/pandoc/pandoc-lua-marshal + commit: a2a97e2af78326ea7841101d4ef56e74426b66c4 ghc-options: "$locals": -fhide-source-paths -Wno-missing-home-modules resolver: lts-20.6 diff --git a/test/Tests/Readers/Org/Block/Figure.hs b/test/Tests/Readers/Org/Block/Figure.hs index 9cf5b91a5..95cb38994 100644 --- a/test/Tests/Readers/Org/Block/Figure.hs +++ b/test/Tests/Readers/Org/Block/Figure.hs @@ -15,31 +15,34 @@ module Tests.Readers.Org.Block.Figure (tests) where import Test.Tasty (TestTree) import Tests.Helpers ((=?>)) import Tests.Readers.Org.Shared ((=:)) -import Text.Pandoc.Builder (image, imageWith, para) +import Text.Pandoc.Builder ( emptyCaption, figure, figureWith, image + , plain, simpleCaption, simpleFigure ) import qualified Data.Text as T tests :: [TestTree] tests = [ "Figure" =: - T.unlines [ "#+caption: A very courageous man." - , "#+name: goodguy" + T.unlines [ "#+caption: A courageous man." + , "#+name: ed" , "[[file:edward.jpg]]" ] =?> - para (image "edward.jpg" "fig:goodguy" "A very courageous man.") + figure (plainCaption "A courageous man.") + (plain $ image "edward.jpg" "ed" "") , "Figure with no name" =: T.unlines [ "#+caption: I've been through the desert on this" , "[[file:horse.png]]" ] =?> - para (image "horse.png" "fig:" "I've been through the desert on this") + figure (plainCaption "I've been through the desert on this") + (plain $ image "horse.png" "" "") , "Figure with `fig:` prefix in name" =: T.unlines [ "#+caption: Used as a metapher in evolutionary biology." , "#+name: fig:redqueen" , "[[./the-red-queen.jpg]]" ] =?> - para (image "./the-red-queen.jpg" "fig:redqueen" - "Used as a metapher in evolutionary biology.") + figure (plainCaption "Used as a metapher in evolutionary biology.") + (plain $ image "./the-red-queen.jpg" "fig:redqueen" "") , "Figure with HTML attributes" =: T.unlines [ "#+caption: mah brain just explodid" @@ -48,28 +51,33 @@ tests = , "[[file:lambdacat.jpg]]" ] =?> let kv = [("style", "color: blue"), ("role", "button")] - name = "fig:lambdacat" - caption = "mah brain just explodid" - in para (imageWith (mempty, mempty, kv) "lambdacat.jpg" name caption) + name = "lambdacat" + capt = plain "mah brain just explodid" + in figureWith (mempty, mempty, kv) (simpleCaption capt) + (plain $ image "lambdacat.jpg" name "") , "LaTeX attributes are ignored" =: T.unlines [ "#+caption: Attribute after caption" , "#+attr_latex: :float nil" , "[[file:test.png]]" ] =?> - para (image "test.png" "fig:" "Attribute after caption") + simpleFigure "Attribute after caption" + "test.png" "" , "Labelled figure" =: T.unlines [ "#+caption: My figure" , "#+label: fig:myfig" , "[[file:blub.png]]" ] =?> - let attr = ("fig:myfig", mempty, mempty) - in para (imageWith attr "blub.png" "fig:" "My figure") + figureWith ("fig:myfig", mempty, mempty) + (simpleCaption $ plain "My figure") + (plain (image "blub.png" "" "")) , "Figure with empty caption" =: T.unlines [ "#+caption:" , "[[file:guess.jpg]]" ] =?> - para (image "guess.jpg" "fig:" "") + figure emptyCaption (plain (image "guess.jpg" "" "")) ] + where + plainCaption = simpleCaption . plain diff --git a/test/Tests/Writers/JATS.hs b/test/Tests/Writers/JATS.hs index e34f6481b..8259c644e 100644 --- a/test/Tests/Writers/JATS.hs +++ b/test/Tests/Writers/JATS.hs @@ -88,7 +88,7 @@ tests = , " <fig>" , " <caption><p>caption</p></caption>" , " <graphic mimetype=\"image\" mime-subtype=\"png\"" <> - " xlink:href=\"a.png\" xlink:title=\"\" />" + " xlink:href=\"a.png\" />" , " </fig>" , " </p>" , " </list-item>" diff --git a/test/command/2118.md b/test/command/2118.md index 8be5c4886..63611c8cb 100644 --- a/test/command/2118.md +++ b/test/command/2118.md @@ -7,11 +7,16 @@ \label{fig:setminus} \end{figure} ^D -[ Para - [ Image - ( "fig:setminus" , [] , [ ( "width" , "80%" ) ] ) - [ Str "Set" , Space , Str "subtraction" ] - ( "setminus.png" , "fig:" ) +[ Figure + ( "fig:setminus" , [] , [] ) + (Caption + Nothing [ Plain [ Str "Set" , Space , Str "subtraction" ] ]) + [ Plain + [ Image + ( "" , [] , [ ( "width" , "80%" ) ] ) + [] + ( "setminus.png" , "" ) + ] ] ] ``` diff --git a/test/command/3577.md b/test/command/3577.md index 2caeb7c11..3c42c3490 100644 --- a/test/command/3577.md +++ b/test/command/3577.md @@ -16,12 +16,15 @@ \end{figure} ^D <figure> -<img src="img1.jpg" alt="Caption 1" /> -<figcaption aria-hidden="true">Caption 1</figcaption> +<figure> +<img src="img1.jpg" /> +<figcaption>Caption 1</figcaption> </figure> <figure> -<img src="img2.jpg" alt="Caption 2" /> -<figcaption aria-hidden="true">Caption 2</figcaption> +<img src="img2.jpg" /> +<figcaption>Caption 2</figcaption> +</figure> +<figcaption>Subfigure with Subfloat</figcaption> </figure> ``` ``` @@ -32,7 +35,7 @@ \end{figure} ^D <figure> -<img src="img1.jpg" alt="Caption 3" /> -<figcaption aria-hidden="true">Caption 3</figcaption> +<img src="img1.jpg" /> +<figcaption>Caption 3</figcaption> </figure> ``` diff --git a/test/command/4183.md b/test/command/4183.md index 8d6c65a01..e844f6a4d 100644 --- a/test/command/4183.md +++ b/test/command/4183.md @@ -4,7 +4,13 @@ <img src="foo" alt="bar"> </figure> ^D -[ Para [ Image ( "" , [] , [] ) [] ( "foo" , "fig:" ) ] ] +[ Figure + ( "" , [] , [] ) + (Caption Nothing []) + [ Plain + [ Image ( "" , [] , [] ) [ Str "bar" ] ( "foo" , "" ) ] + ] +] ``` ``` @@ -18,8 +24,13 @@ </figcaption> </figure> ^D -[ Para - [ Image ( "" , [] , [] ) [ Str "baz" ] ( "foo" , "fig:" ) ] +[ Figure + ( "" , [] , [] ) + (Caption + Nothing [ Div ( "" , [] , [] ) [ Plain [ Str "baz" ] ] ]) + [ Plain + [ Image ( "" , [] , [] ) [ Str "bar" ] ( "foo" , "" ) ] + ] ] ``` @@ -30,9 +41,9 @@ <figcaption><p><em>baz</em></p></figcaption> </figure> ^D -[ Para - [ Image - ( "" , [] , [] ) [ Emph [ Str "baz" ] ] ( "foo" , "fig:" ) - ] +[ Figure + ( "" , [] , [] ) + (Caption Nothing [ Para [ Emph [ Str "baz" ] ] ]) + [ Plain [ Image ( "" , [] , [] ) [] ( "foo" , "" ) ] ] ] ``` diff --git a/test/command/4420.md b/test/command/4420.md index 36d697234..9d809a106 100644 --- a/test/command/4420.md +++ b/test/command/4420.md @@ -2,10 +2,8 @@ % pandoc -f native -t rst [Para [Image ("",["align-right"],[("width","100px")]) [Str "image"] ("foo.png","fig:test")]] ^D -.. figure:: foo.png - :alt: test +.. image:: foo.png + :alt: image :align: right :width: 100px - - image ``` diff --git a/test/command/4677.md b/test/command/4677.md index 64c436005..15c8fd5ee 100644 --- a/test/command/4677.md +++ b/test/command/4677.md @@ -2,8 +2,8 @@ % pandoc --to "markdown-bracketed_spans-fenced_divs-link_attributes-simple_tables-multiline_tables-grid_tables-pipe_tables-fenced_code_attributes-markdown_in_html_blocks-table_captions-smart" {#img:1} ^D -<figure> -<img src="img.png" id="img:1" alt="Caption" /> +<figure id="img:1"> +<img src="img.png" alt="Caption" /> <figcaption aria-hidden="true">Caption</figcaption> </figure> ``` diff --git a/test/command/5321.md b/test/command/5321.md index 975852482..43e0ddc74 100644 --- a/test/command/5321.md +++ b/test/command/5321.md @@ -7,9 +7,14 @@ <graphic xlink:href="foo.png" xlink:alt-text="baz" /> </fig> ^D -[ Para - [ Image - ( "fig-1" , [] , [] ) [ Str "bar" ] ( "foo.png" , "fig:" ) +[ Figure + ( "fig-1" , [] , [] ) + (Caption Nothing [ Plain [ Str "bar" ] ]) + [ Div + ( "" , [ "caption" ] , [] ) + [ Header 6 ( "" , [] , [] ) [] , Para [ Str "bar" ] ] + , Para + [ Image ( "" , [] , [] ) [ Str "baz" ] ( "foo.png" , "" ) ] ] ] ``` @@ -24,11 +29,17 @@ <graphic xlink:href="foo.png" xlink:alt-text="baz" /> </fig> ^D -[ Para - [ Image - ( "fig-1" , [] , [] ) - [ Str "foo" , LineBreak , Str "bar" ] - ( "foo.png" , "fig:" ) +[ Figure + ( "fig-1" , [] , [] ) + (Caption + Nothing [ Plain [ Str "foo" , LineBreak , Str "bar" ] ]) + [ Div + ( "" , [ "caption" ] , [] ) + [ Header 6 ( "" , [] , [] ) [ Str "foo" ] + , Para [ Str "bar" ] + ] + , Para + [ Image ( "" , [] , [] ) [ Str "baz" ] ( "foo.png" , "" ) ] ] ] ``` diff --git a/test/command/5368.md b/test/command/5368.md index e8b54bf7b..9e09cee6a 100644 --- a/test/command/5368.md +++ b/test/command/5368.md @@ -15,21 +15,32 @@ Quux. [ OrderedList ( 1 , Decimal , Period ) [ [ Para [ Str "foo" ] - , Para - [ Image - ( "" , [] , [] ) [ Str "bar" ] ( "bar.png" , "fig:" ) + , Figure + ( "" , [] , [] ) + (Caption Nothing [ Plain [ Str "bar" ] ]) + [ Plain + [ Image ( "" , [] , [] ) [ Str "bar" ] ( "bar.png" , "" ) + ] ] ] , [ Para [ Str "foo2" ] - , Para - [ Image - ( "" , [] , [] ) [ Str "bar2" ] ( "bar2.png" , "fig:" ) + , Figure + ( "" , [] , [] ) + (Caption Nothing [ Plain [ Str "bar2" ] ]) + [ Plain + [ Image + ( "" , [] , [] ) [ Str "bar2" ] ( "bar2.png" , "" ) + ] ] ] , [ Para [ Str "foo3" ] - , Para - [ Image - ( "" , [] , [] ) [ Str "foo3" ] ( "foo3.png" , "fig:" ) + , Figure + ( "" , [] , [] ) + (Caption Nothing [ Plain [ Str "foo3" ] ]) + [ Plain + [ Image + ( "" , [] , [] ) [ Str "foo3" ] ( "foo3.png" , "" ) + ] ] ] ] diff --git a/test/command/5619.md b/test/command/5619.md index 0f612ea67..7eec80cfd 100644 --- a/test/command/5619.md +++ b/test/command/5619.md @@ -6,32 +6,40 @@ The caption. Here's what piggybacking on caption would look like {#fig:1} ^D -[ Para - [ Image - ( "test" , [] , [ ( "width" , "1in" ) ] ) - [ Str "The" - , Space - , Str "caption." - , Space - , Str "Here's" - , Space - , Str "what" - , Space - , Str "piggybacking" - , Space - , Str "on" - , Space - , Str "caption" - , Space - , Str "would" - , Space - , Str "look" - , Space - , Str "like" - , Space - , Str "{#fig:1}" +[ Figure + ( "" , [] , [] ) + (Caption + Nothing + [ Plain + [ Str "The" + , Space + , Str "caption." + , Space + , Str "Here's" + , Space + , Str "what" + , Space + , Str "piggybacking" + , Space + , Str "on" + , Space + , Str "caption" + , Space + , Str "would" + , Space + , Str "look" + , Space + , Str "like" + , Space + , Str "{#fig:1}" + ] + ]) + [ Plain + [ Image + ( "test" , [] , [ ( "width" , "1in" ) ] ) + [ Str "img1.jpg" ] + ( "img1.jpg" , "" ) ] - ( "img1.jpg" , "fig:" ) ] ] ``` diff --git a/test/command/6137.md b/test/command/6137.md index a58b4876f..077044e07 100644 --- a/test/command/6137.md +++ b/test/command/6137.md @@ -134,24 +134,32 @@ This reference to Figure \ref{fig:label} works fine. , 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." +, Figure + ( "fig:label" , [] , [] ) + (Caption + Nothing + [ Plain + [ Str "A" + , Space + , Str "numbered" + , Space + , Str "caption," + , Space + , Str "if" + , Space + , Str "I" + , Space + , Str "use" + , Space + , Str "pandoc-crossref." + ] + ]) + [ Plain + [ Image + ( "" , [] , [ ( "width" , "\\textwidth" ) ] ) + [] + ( "example.png" , "" ) ] - ( "example.png" , "fig:" ) ] ] ``` diff --git a/test/command/6774.md b/test/command/6774.md index 66549c0f2..7e8db5b50 100644 --- a/test/command/6774.md +++ b/test/command/6774.md @@ -13,7 +13,7 @@ Chapter</text:span></text:a></text:p> % pandoc -f native -t opendocument+xrefs_name --quiet [Header 1 ("chapter1",[],[]) [Str "The",Space,Str "Chapter"] ,Para [Str "Chapter",Space,Str "1",Space,Str "references",Space,Link ("",[],[]) [Str "The",Space,Str "Chapter"] ("#chapter1","")] -,Para [Image ("lalune",[],[]) [Str "lalune"] ("lalune.jpg","fig:Voyage dans la Lune")] +,Figure ("lalune",[],[]) (Caption Nothing [Para [Str "Voyage dans la Lune"]]) [Plain [Image ("",[],[]) [Str "lalune"] ("lalune.jpg","")]] ,Para [Str "Image",Space,Str "1",Space,Str "references",Space,Link ("",[],[]) [Str "La",Space,Str "Lune"] ("#lalune","")]] ^D <text:h text:style-name="Heading_20_1" text:outline-level="1"><text:bookmark-start text:name="chapter1" />The @@ -22,7 +22,7 @@ Chapter<text:bookmark-end text:name="chapter1" /></text:h> <text:bookmark-ref text:reference-format="text" text:ref-name="chapter1">The Chapter</text:bookmark-ref></text:p> <text:p text:style-name="FigureWithCaption"><draw:frame draw:name="img1"><draw:image xlink:href="lalune.jpg" xlink:type="simple" xlink:show="embed" xlink:actuate="onLoad" /></draw:frame></text:p> -<text:p text:style-name="FigureCaption">lalune</text:p> +<text:p text:style-name="FigureCaption">Voyage dans la Lune</text:p> <text:p text:style-name="Text_20_body">Image 1 references <text:sequence-ref text:reference-format="caption" text:ref-name="lalune">La Lune</text:sequence-ref></text:p> @@ -31,7 +31,7 @@ Lune</text:sequence-ref></text:p> % pandoc -f native -t opendocument+xrefs_number --quiet [Header 1 ("chapter1",[],[]) [Str "The",Space,Str "Chapter"] ,Para [Str "Chapter",Space,Str "1",Space,Str "references",Space,Link ("",[],[]) [Str "The",Space,Str "Chapter"] ("#chapter1","")] -,Para [Image ("lalune",[],[]) [Str "lalune"] ("lalune.jpg","fig:Voyage dans la Lune")] +,Figure ("lalune",[],[]) (Caption Nothing [Para [Str "lalune"]]) [Plain [Image ("",[],[]) [Str "lalune"] ("lalune.jpg","Voyage dans la Lune")]] ,Para [Str "Image",Space,Str "1",Space,Str "references",Space,Link ("",[],[]) [Str "La",Space,Str "Lune"] ("#lalune","")]] ^D <text:h text:style-name="Heading_20_1" text:outline-level="1"><text:bookmark-start text:name="chapter1" />The @@ -47,7 +47,7 @@ Chapter<text:bookmark-end text:name="chapter1" /></text:h> % pandoc -f native -t opendocument+xrefs_number+xrefs_name --quiet [Header 1 ("chapter1",[],[]) [Str "The",Space,Str "Chapter"] ,Para [Str "Chapter",Space,Str "1",Space,Str "references",Space,Link ("",[],[]) [Str "The",Space,Str "Chapter"] ("#chapter1","")] -,Para [Image ("lalune",[],[]) [Str "lalune"] ("lalune.jpg","fig:Voyage dans la Lune")] +,Figure ("lalune",[],[]) (Caption Nothing [Para [Str "Voyage dans la Lune"]]) [Plain [Image ("",[],[]) [Str "lalune"] ("lalune.jpg","")]] ,Para [Str "Image",Space,Str "1",Space,Str "references",Space,Link ("",[],[]) [Str "La",Space,Str "Lune"] ("#lalune","")]] ^D <text:h text:style-name="Heading_20_1" text:outline-level="1"><text:bookmark-start text:name="chapter1" />The @@ -56,7 +56,7 @@ Chapter<text:bookmark-end text:name="chapter1" /></text:h> <text:bookmark-ref text:reference-format="number" text:ref-name="chapter1"></text:bookmark-ref><text:s /><text:bookmark-ref text:reference-format="text" text:ref-name="chapter1">The Chapter</text:bookmark-ref></text:p> <text:p text:style-name="FigureWithCaption"><draw:frame draw:name="img1"><draw:image xlink:href="lalune.jpg" xlink:type="simple" xlink:show="embed" xlink:actuate="onLoad" /></draw:frame></text:p> -<text:p text:style-name="FigureCaption">lalune</text:p> +<text:p text:style-name="FigureCaption">Voyage dans la Lune</text:p> <text:p text:style-name="Text_20_body">Image 1 references <text:sequence-ref text:reference-format="value" text:ref-name="lalune"></text:sequence-ref><text:s /><text:sequence-ref text:reference-format="caption" text:ref-name="lalune">La Lune</text:sequence-ref></text:p> diff --git a/test/command/figures-context.md b/test/command/figures-context.md new file mode 100644 index 000000000..1f93d63ff --- /dev/null +++ b/test/command/figures-context.md @@ -0,0 +1,48 @@ +# Figure with one image, caption and label + +``` +% pandoc -t context -f html +<figure> + <img src="mandrill.jpg" /> + <figcaption><q>The Mandrill</q>, a photo used in + image processing tests.</figcaption> +</figure> +^D +\startplacefigure[title={\quotation{The Mandrill}, a photo used in image +processing tests.}] +{\externalfigure[mandrill.jpg]} +\stopplacefigure +``` + +# Nested figures + +``` +% pandoc -t context -f html +<figure id="test-images"> + <figure id="mandrill"> + <img src="../testing/mandrill.jpg"> + <figcaption><q>The Mandrill</q> is a commonly used test image.</figcaption> + </figure> + <figure id="peppers"> + <img src="../testing/peppers.webp" > + <figcaption>Another test image. This one is called <q>peppers</q>.</figcaption> + </figure> + <figcaption>Signal processing test images.</figcaption> +</figure> +^D +\startplacefigure[reference=test-images,title={Signal processing test +images.}] +\startfloatcombination +\startplacefigure[reference=mandrill,title={\quotation{The Mandrill} is +a commonly used test image.}] +{\externalfigure[../testing/mandrill.jpg]} +\stopplacefigure + +\startplacefigure[reference=peppers,title={Another test image. This one +is called \quotation{peppers}.}] +{\externalfigure[../testing/peppers.webp]} +\stopplacefigure + +\stopfloatcombination +\stopplacefigure +``` diff --git a/test/command/figures-fb2.md b/test/command/figures-fb2.md new file mode 100644 index 000000000..63aa86dc9 --- /dev/null +++ b/test/command/figures-fb2.md @@ -0,0 +1,8 @@ +``` +% pandoc -f native -t fb2 +[Figure ("fig-id",[],[]) (Caption Nothing []) [Para [Str "content"]]] + +^D +<?xml version="1.0" encoding="UTF-8"?> +<FictionBook xmlns="http://www.gribuser.ru/xml/fictionbook/2.0" xmlns:l="http://www.w3.org/1999/xlink"><description><title-info><genre>unrecognised</genre></title-info><document-info><program-used>pandoc</program-used></document-info></description><body><title><p /></title><section><p>content</p></section></body></FictionBook> +``` diff --git a/test/command/figures-haddock.md b/test/command/figures-haddock.md new file mode 100644 index 000000000..9a63861d7 --- /dev/null +++ b/test/command/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-html.md b/test/command/figures-html.md new file mode 100644 index 000000000..3718246d1 --- /dev/null +++ b/test/command/figures-html.md @@ -0,0 +1,92 @@ +# Writer + +HTML5 figure with caption and content. + +``` +% pandoc -f native -t html5 +[Figure ("fig-id",[],[]) (Caption Nothing [Plain [Str "caption"]]) [Para [Str "content"]]] + +^D +<figure id="fig-id"> +<p>content</p> +<figcaption>caption</figcaption> +</figure> +``` + +HTML5 figure with NO caption and content. + +``` +% pandoc -f native -t html5 +[Figure ("fig-id",[],[]) (Caption Nothing []) [Para [Str "content"]]] + +^D +<figure id="fig-id"> +<p>content</p> +</figure> +``` + +HTML4 figure with caption and content. + +``` +% pandoc -f native -t html4 +[Figure ("fig-id",[],[]) (Caption Nothing [Plain [Str "caption"]]) [Para [Str "content"]]] + +^D +<div class="float" id="fig-id"> +<p>content</p> +<div class="figcaption">caption</div> +</div> +``` + +HTML4 figure with NO caption and content. + +``` +% pandoc -f native -t html4 +[Figure ("fig-id",[],[]) (Caption Nothing []) [Para [Str "content"]]] + +^D +<div class="float" id="fig-id"> +<p>content</p> +</div> +``` + +# Reader + +Figure with caption and multiple elements. + +``` +% pandoc -f html -t native +<figure class="important"> + <img src="../media/rId25.jpg" /> + <ul> <li> ITEM </li> </ul> + <figcaption> CAP2 </figcaption> +</figure> +^D +[ Figure + ( "" , [ "important" ] , [] ) + (Caption Nothing [ Plain [ Str "CAP2" ] ]) + [ Plain + [ Image ( "" , [] , [] ) [] ( "../media/rId25.jpg" , "" ) ] + , BulletList [ [ Plain [ Str "ITEM" ] ] ] + ] +] +``` + +Figure without caption. + +``` +% pandoc -f html -t native +<figure class="important"> + <img src="../media/rId25.jpg" /> + <ul> <li> ITEM </li> </ul> +</figure> +^D +[ Figure + ( "" , [ "important" ] , [] ) + (Caption Nothing []) + [ Plain + [ Image ( "" , [] , [] ) [] ( "../media/rId25.jpg" , "" ) ] + , BulletList [ [ Plain [ Str "ITEM" ] ] ] + ] +] +``` diff --git a/test/command/figures-jats.md b/test/command/figures-jats.md new file mode 100644 index 000000000..a5089df2a --- /dev/null +++ b/test/command/figures-jats.md @@ -0,0 +1,14 @@ +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 +<fig id="fig-id"> + <caption><p>Caption</p></caption> + <p>Text</p> + <graphic id="fig-id-2" mimetype="image" mime-subtype="png" xlink:href="foo.png" xlink:title="fig:" /> +</fig> +``` diff --git a/test/command/figures-jira.md b/test/command/figures-jira.md new file mode 100644 index 000000000..7517b7e0b --- /dev/null +++ b/test/command/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-latex.md b/test/command/figures-latex.md new file mode 100644 index 000000000..cebce971e --- /dev/null +++ b/test/command/figures-latex.md @@ -0,0 +1,83 @@ +# Figure with one image, caption and label + +``` +% pandoc -f latex -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 -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-markdown.md b/test/command/figures-markdown.md new file mode 100644 index 000000000..4d3ea4185 --- /dev/null +++ b/test/command/figures-markdown.md @@ -0,0 +1,12 @@ +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 +<figure id="fig-id"> +<p><img src="foo.png" title="fig:" /></p> +<figcaption><p>Caption</p></figcaption> +</figure> +``` diff --git a/test/command/figures-mediawiki.md b/test/command/figures-mediawiki.md new file mode 100644 index 000000000..63bb2a96d --- /dev/null +++ b/test/command/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 +<div id="fig-id" class="figure"> + +[[File:foo.png|thumb|none]] + + +</div> +``` diff --git a/test/command/figures-org.md b/test/command/figures-org.md new file mode 100644 index 000000000..bfa5c6de1 --- /dev/null +++ b/test/command/figures-org.md @@ -0,0 +1,16 @@ +``` +% pandoc -f native -t org +[Figure ("fig-id",[],[]) (Caption Nothing []) [Para [Str "content"]]] + +^D +<<fig-id>> +content +``` + +``` +% pandoc -f native -t org +[Figure ("",[],[]) (Caption Nothing []) [Para [Str "content"]]] + +^D +content +``` diff --git a/test/command/figures-rst.md b/test/command/figures-rst.md new file mode 100644 index 000000000..fac1145ad --- /dev/null +++ b/test/command/figures-rst.md @@ -0,0 +1,10 @@ +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 +.. figure:: foo.png + :alt: fig: +``` diff --git a/test/command/figures-texinfo.md b/test/command/figures-texinfo.md new file mode 100644 index 000000000..f50c6b5bb --- /dev/null +++ b/test/command/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,,,,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-textile.md b/test/command/figures-textile.md new file mode 100644 index 000000000..27c60cbe8 --- /dev/null +++ b/test/command/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 +<figure id="fig-id"> + +<figcaption> + +Caption + +</figcaption> + +!foo.png! + + +</figure> +``` + +``` +% pandoc -f native -t textile +[Figure ("fig-id",[],[]) (Caption Nothing []) [Para [Image ("",[],[]) [] ("foo.png", "")]]] + +^D +<figure id="fig-id"> + +!foo.png! + + +</figure> +``` diff --git a/test/command/figures-xwiki.md b/test/command/figures-xwiki.md new file mode 100644 index 000000000..0b4e84dc6 --- /dev/null +++ b/test/command/figures-xwiki.md @@ -0,0 +1,10 @@ +``` +% 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-zimwiki.md b/test/command/figures-zimwiki.md new file mode 100644 index 000000000..a2d4bcd9a --- /dev/null +++ b/test/command/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/html-read-figure.md b/test/command/html-read-figure.md index d7eb96bb4..9d7cc163a 100644 --- a/test/command/html-read-figure.md +++ b/test/command/html-read-figure.md @@ -5,9 +5,11 @@ <figcaption>bar</figcaption> </figure> ^D -[ Para - [ Image - ( "" , [] , [] ) [ Str "bar" ] ( "foo.png" , "fig:voyage" ) +[ Figure + ( "" , [] , [] ) + (Caption Nothing [ Plain [ Str "bar" ] ]) + [ Plain + [ Image ( "" , [] , [] ) [] ( "foo.png" , "voyage" ) ] ] ] ``` @@ -19,9 +21,11 @@ <img src="foo.png" title="voyage"> </figure> ^D -[ Para - [ Image - ( "" , [] , [] ) [ Str "bar" ] ( "foo.png" , "fig:voyage" ) +[ Figure + ( "" , [] , [] ) + (Caption Nothing [ Plain [ Str "bar" ] ]) + [ Plain + [ Image ( "" , [] , [] ) [] ( "foo.png" , "voyage" ) ] ] ] ``` @@ -32,8 +36,12 @@ <img src="foo.png" title="voyage"> </figure> ^D -[ Para - [ Image ( "" , [] , [] ) [] ( "foo.png" , "fig:voyage" ) ] +[ Figure + ( "" , [] , [] ) + (Caption Nothing []) + [ Plain + [ Image ( "" , [] , [] ) [] ( "foo.png" , "voyage" ) ] + ] ] ``` @@ -44,9 +52,11 @@ <figcaption>bar</figcaption> </figure> ^D -[ Para - [ Image - ( "" , [] , [] ) [ Str "bar" ] ( "foo.png" , "fig:voyage" ) +[ Figure + ( "" , [] , [] ) + (Caption Nothing [ Plain [ Str "bar" ] ]) + [ Para + [ Image ( "" , [] , [] ) [] ( "foo.png" , "voyage" ) ] ] ] ``` @@ -55,11 +65,17 @@ % pandoc -f html -t native <figure><img src="foo.png" title="voyage" alt="this is ignored"><figcaption>bar <strong>baz</strong></figcaption></figure> ^D -[ Para - [ Image - ( "" , [] , [] ) - [ Str "bar" , Space , Strong [ Str "baz" ] ] - ( "foo.png" , "fig:voyage" ) +[ Figure + ( "" , [] , [] ) + (Caption + Nothing + [ Plain [ Str "bar" , Space , Strong [ Str "baz" ] ] ]) + [ Plain + [ Image + ( "" , [] , [] ) + [ Str "this" , Space , Str "is" , Space , Str "ignored" ] + ( "foo.png" , "voyage" ) + ] ] ] ``` diff --git a/test/command/jats-figure-alt-text.md b/test/command/jats-figure-alt-text.md index 229e52eda..d1ff67087 100644 --- a/test/command/jats-figure-alt-text.md +++ b/test/command/jats-figure-alt-text.md @@ -8,11 +8,15 @@ <graphic xlink:href="foo.png" xlink:alt-text="baz" /> </fig> ^D -[ Para - [ Image - ( "fig-1" , [] , [ ( "alt" , "alternative-decription" ) ] ) - [ Str "bar" ] - ( "foo.png" , "fig:" ) +[ Figure + ( "fig-1" , [] , [] ) + (Caption Nothing [ Plain [ Str "bar" ] ]) + [ Div + ( "" , [ "caption" ] , [] ) + [ Header 6 ( "" , [] , [] ) [] , Para [ Str "bar" ] ] + , Plain [ Str "alternative-decription" ] + , Para + [ Image ( "" , [] , [] ) [ Str "baz" ] ( "foo.png" , "" ) ] ] ] ``` diff --git a/test/command/refs.md b/test/command/refs.md index c6457be4c..cf2395fb8 100644 --- a/test/command/refs.md +++ b/test/command/refs.md @@ -133,11 +133,12 @@ Accuracy~\eqref{eq:Accuracy} is the proportion, measuring true results among all Figure \ref{fig:Logo} illustrated the SVG logo ^D -[ Para - [ Image - ( "fig:Logo" , [] , [] ) - [ Str "Logo" ] - ( "command/SVG_logo.svg" , "fig:" ) +[ Figure + ( "fig:Logo" , [] , [] ) + (Caption Nothing [ Plain [ Str "Logo" ] ]) + [ Plain + [ Image ( "" , [] , [] ) [] ( "command/SVG_logo.svg" , "" ) + ] ] , Para [ Str "Figure" @@ -195,25 +196,28 @@ Figure \ref{fig:Logo2} illustrated the SVG logo Figure \ref{fig:Logo3} illustrated the SVG logo ^D [ Header 1 ( "one" , [] , [] ) [ Str "One" ] -, Para - [ Image - ( "fig:Logo" , [] , [] ) - [ Str "Logo" ] - ( "command/SVG_logo.svg" , "fig:" ) +, Figure + ( "fig:Logo" , [] , [] ) + (Caption Nothing [ Plain [ Str "Logo" ] ]) + [ Plain + [ Image ( "" , [] , [] ) [] ( "command/SVG_logo.svg" , "" ) + ] ] -, Para - [ Image - ( "fig:Logo2" , [] , [] ) - [ Str "Logo2" ] - ( "command/SVG_logo2.svg" , "fig:" ) +, Figure + ( "fig:Logo2" , [] , [] ) + (Caption Nothing [ Plain [ Str "Logo2" ] ]) + [ Plain + [ Image ( "" , [] , [] ) [] ( "command/SVG_logo2.svg" , "" ) + ] ] , Header 1 ( "two" , [] , [] ) [ Str "Two" ] , Header 2 ( "subone" , [] , [] ) [ Str "Subone" ] -, Para - [ Image - ( "fig:Logo3" , [] , [] ) - [ Str "Logo3" ] - ( "command/SVG_logo3.svg" , "fig:" ) +, Figure + ( "fig:Logo3" , [] , [] ) + (Caption Nothing [ Plain [ Str "Logo3" ] ]) + [ Plain + [ Image ( "" , [] , [] ) [] ( "command/SVG_logo3.svg" , "" ) + ] ] , Para [ Str "Figure" diff --git a/test/docx/golden/image.docx b/test/docx/golden/image.docx Binary files differindex 099f705e4..0b9a688fd 100644 --- a/test/docx/golden/image.docx +++ b/test/docx/golden/image.docx diff --git a/test/fb2/images-embedded.fb2 b/test/fb2/images-embedded.fb2 index d647005ad..57a1e0370 100644 --- a/test/fb2/images-embedded.fb2 +++ b/test/fb2/images-embedded.fb2 @@ -1,2 +1,2 @@ <?xml version="1.0" encoding="UTF-8"?> -<FictionBook xmlns="http://www.gribuser.ru/xml/fictionbook/2.0" xmlns:l="http://www.w3.org/1999/xlink"><description><title-info><genre>unrecognised</genre></title-info><document-info><program-used>pandoc</program-used></document-info></description><body><title><p /></title><section><image l:href="#image1" l:type="inlineImageType" alt="This image was embedded using data URI scheme" /><p>This image was embedded using data URI scheme</p></section></body><binary id="image1" content-type="image/png">iVBORw0KGgoAAAANSUhEUgAAADAAAAAgCAIAAADbtmxLAAABmGlDQ1BpY2MAAHjapdG/axMBGMbxTy4tldJSwSAiHW4ootKCqIOrVShIkRIrJNUluUvaQi4Nd1dEXAQHF4cOXVRcLOLirJv4BygIggqCi7sUBRcpcbiDgtBBfOGF5/315eV9qR7qRUk2EpL087S+MB82mivh2BeBcUcddrwVZYOLS0uLDrRfH1Xgw1wvSjL/ZpNxJ4uohFiKBmlOZYC7t/JBTmUXtWitFROMYDZtNFcIzqDWLvRl1FYL3UAtXa5fIughXC30A4TtQr9AGK2lCcFbzMRJPybYxWScxDFVGE16m1G5ZwUTnf71aziPaXUsYB4h2tjEOnrIMVfG/QJyAC/GtKvYKFlRqQe4jbTkrGKtZM+WvZvI0CnjbtnfKb1XMtBoroR//yzrnjtbbDRxhdFvw+HP04w9Zu/+cPj76XC4t0P1M2+29+c3trnwnerWfm7mCVP3ePl6P9d+xqstjn0dtNIWitMG3S4/njPZ5Mh7xm/8b734Z1m384nlOyy+4+EjTnSZunkyzsP1ft5J+63eKWT1hXn4AzDofghlJQBJAAAACXBIWXMAAAsSAAALEgHS3X78AAACInpUWHRSYXcgcHJvZmlsZSB0eXBlIGV4aWYAAHjahVRJtiQhCNx7ijpCMIhyHNPU9/oGffxeaNY3p/5VC5IAQkAhtL9/evh8Pp+PiwaNKZubAYDuugNcMH4ZIAN6A6ATo68kdAA8VQ1DkoEIq2EILiBiALIQDTISWvz3SSQNJHwnilWTGgC/ZMSa1Fc8TDznZH4rgWOtRrwQKGh8VyNZ8bAY9Ccj1EGXUI0JwNE3n3itxrzis7Sq1TgBiNMwesKo1TjfcdZqXBaiWRpLrcbbEjBLU63G9QGv1bit+CSKWi2W8+3QLDluF/wIBgBEaNQWNSjFzHj7/zgOP92EBap3v2BqlNi2pEbGVi0yBNwkcRPiTVxIJDVLRgJxEXGLRgAgLBASkiIIwlIEYgyBJCnC4lKExN6yGSW6SD961nvvQaxhBZq4rbptbX1HlJPSokN37t9m9957a5utDux7Xwk06WnWWOJ2yqgkPqW4e2urnmNPK0HMtq0Hkkc7ZbSXUleHiNMIoGy7r/ppEwAIV+Amv1rS/3ghgCz23ns+m/HrASdJMWT2chsBiS2z73fcLGd+3E8hZ05nQ81zzOW2n8Saj1VzwTMHZ+g6xcPg5ozLASM7Z/hl9kaPnPFQmrcyvm8lFKbrAQwAoegtYFy34rEXRSFP/qEo4tmQ0wywlwPyG5G/BJQXvF5wOR4k7m9HjlupR/y6Mp42RjhWxm+Oh99BvMrwD3UCiGvkpxuRAAAACXZwQWcAAAAwAAAAIACELJ4GAAALGklEQVRYw11YW48dV1b+1tq7qs6t+/TldPsSx3bbcRwncWY0A4LMCOYFXpgHJCR4QvwAnpAQj/wB/gR/ACR4QUKDECMUEjLOZew4zsRxuu122+52n9Pnfuqy9/p4qNNtD1tLpVKpap/vrMu31rdl/nAgIjSpF0kAJAEHGJwAAIQheqeARVqomCQZGUkjSYLmTAyAkCJiESRVNYQAaL3h8k3SzPj6MjEzsr7SqyoAcRABQItRVZ14kqifmNEkTZNiUZiZ934xm4WE3mva8GYGAA5UJ8YYIyCipiKk1ZuTBAhQBGZQFRKvTAgBaQBIeOekBqpa+0gBxFgAlmhqhixJzUKMRVEUx/3RWmel3z9xzrVX2+tuRb3WnrDKVFUEgKlCVWI055WMZ76AieipX0AYzYwQUZqZqJD0tKCqFJAxhKiqSZKooirj06fPMt/odlezhngFYar+0e7jxWLR6/Vc7ubzpNnM4BlDSDLvvQ8hnAYFIlCFRUDEjASgIGFGEcBIoSrMCFAVhgiKTxJPkgJVSeBBhKqaTCb5Ip4cD/efPP/g9q2soSvdTp7nAuv2Vk/2BoHFyWgRYxVjbDezRiMDMicNxqCqqhIZVZxZVK3zaRkgXYaMdeDMoMoapSpo8GSE1t6ihaCqPs3WV/VwPpxOp8fHRw++cUmq7XYzSbLV1W5vu3fw7Emn0xwcD+ZzF8vKQtlI09R7J6SXOldgEDEwAmdguMyYV/lEVWEkARExEkoVBxHWxeUSFefK6fTJ48dlme/sXN7a3vjVnf8NIQ6Hk1ajOZ+Nf/3ZZ9Uij0V+fedqM0v2nz5ut7LtCz1GC2WVJqmry1KgZKLqlbo0qLPanJrAVKgSRX/LPElxQF0smiDy6Ojo7pd3qXLjxo2r1y8fnwxORpN8Nt/u9fLF5OTFcRVKDWE0HJZF2O71IsOzZ0+e7D3tdDo7168miU9SJ6IhBIGD2KuKMpHaPwoFXkXq9Aak+/u//TsFRCEgEAljjFtbW+UiHPb765sbJ8M+Y9HtdAbDgWs0pSge7O1u9Tar+Xwwmy0m03I0XpgbjydZlk2n43armaVOJIqQDEIIIKBABK/iBYuAnT4HwJrx1CkhRosAIRBBo93ImunO25dv/eBmb231+rUrRTH/we1ba+udhw/uSoZGOzt38Vx/1D85folYLhazqpg3mj5ruNWVTqPhxcEsAOa8ihJiAhMEQVChCgXmhKcWT41O6IGq5kCjqPOTk9F4PF7rrlvKRtQHjx/d2Lk+mgy+evrwhzs3Xuzv0tmbb5z79LNPzm9utdorEoNkzPPx+x+812o10tR7DyCqUwCMQUUIUqm2JOolbb/GjmbwoDGS9GZBnYM4IS0E5+TChS1Nk7Z28uPhW29euvPRf2fN1pdffNE1vXnzxsGgf/B036duvbce5tXG2uZkfnL79q3t8+sA4Rws0CJIAOI8LADUusLqeC0rTl4RJgyg1Fe+fB7yUrxTQoRWVoExbWTjl6P5fD7dO6yIF4P+bDK/92T3hzffLWGffPq5c7K1uf7hj3+PrLqbqxffuDQc9VdWVtY31846l1CFqJlalk8gr/UxAIzLLrZkbVK5WHgHhFIYmS+K6ZhFkY/Hi/5gPOhLUzvnu73L59KVxjyffXH314vFIsbYaTXeuXFtcHx4sPd9S+3l84PMwTsyBrMgQhUIgrEUREWUU4O8uhcLdW45BsWpiVRgoSyYTxYn/ee7e9/f/2Z8eOwYm8pko4EktDvpzOZXL5z3Dd3b2/vi/r1G0795cat//GxrvWPTaW+lvdVdXUkTCaVagAUrF6wKVSAGxIAQJEZYiVjSSrBSq4SVWCFWKINYpQzK4FHmhqjOgbF/+Hx0dJyXtv/46ZuXtrrd1V6ruRhNJqPZlfbq5999/Dt/+LNf/tf/nEyH585t73338OrVS3E8Pnl+MJnOi7i4fG1no7cJ79Sh7vPISwCwZYCERN3TjQCFZFxGE3FJV97iXCGIKBZlcyV799zbIdhsNnvyaP/x3r6Z+Tx02i6Kv/7WO8bFX/3ZT37xyZ2yf9Ta2n73vZ1vf/Xlv338+R/97MOVjc63X99fbXduvfuONBJTAlDxiBGAWKQZSVn2BZ4lDYwAlDQzkF7LEmYQyUSTdkvTzNuiZLz25vlOt3N0cPTwxcH7W2/9+NbN0Uef3Pvs6w/+9KcraePb3+z+6NKF+cHLvvN/89d/2SQsTSdr3clwMh0M1nvr0ki4yI0iQgBSu8dYOwxm4BIEyTrTEY1mHrNpZD3KiMIhlLEokljKWueyytsX3ji/2rqzuzt4Obh95eLd3+ztf7Xv1e2sp8OXw73h8Od//FNNtIh5Rqx322tZWoWimo1c7hQi4mgBxtPpA3VBkXQ0M8BOh5VoS3D8j3+CACqsR4EYzUyIalqaCqCxyIsB/uFf//lPfv93R/2jf/z4m0Zmf/6j977af/wXH/7B6ubK+dVV2+g6D0Yzg4OoA0kRrYoiEXcarFfzq7IueJKsYZktAXl7MRURiARakiQ08xAACHCGybj/i3v3ZoNyDa3/vPPg59cuf/fi4GKjPRmH99cuHT5+Ouv3ipV5b2ve2lxRdfPJLMa4ttKxEEl68ZH52bh4xkDhbLI2OYNiBpL+cHfmnKvfq2nf+eWXi2L+6PgQh42nk+GVc1uf7h9+f1T8ZOftXz76flu7L07Gs7FttCYvknH74PiDt24kjWa/PyvLElupJ2OMZFXBROS3hnoz8sxBS9+YYemhrw9L55xCFCYSalgR7Ehy/+DFnChC0kq3m37j9nr2L7uPnrw8UBb//t2emGsnybW8OW9M3uhc+fbprNWW0Qwh6MwKAQGEEIhlpccYSVLl/wkPM4unqEj6+7MyUZeIpj6pRxOJjDGO5qNpbNLsWTiSyt/dex5mR1Ui+9Phxe72w+moI1mmViSbG7xQNNpHlrhKBnkkcbIwi5WZGegpgMYYq6oCoKoiamZAfB1TWCoq+o/2DxzEiU/TNHXeBCGEqqqKGKGIDPOFTedDY8x8M5HEIRlXi5D7TtrsVpv5cDbZyB69eL7a6IjIfD6NNBHJy1A3tcRJCOV4Nmq1OiqZUgFznonzZVWIECoqXjWpijJGevVipFkZqipYKt6JE1XXjj5tJHk+n41jptrtrifqptNpq9WaTMcqyXon9VlqxHgyi5GjWa6qeZ5DJcsyM6OomVm04WQwnY3XIGkCQGEhzktjORoN8yp3zqVpI0lSUNXB59OhiChE1RdaSK0XSTNqoSSbmQe8F8Bi4jRN00WRr3TY7jSzJAEAQZIkCBUQo1aqmtSTHmJkrGApQtu7lodKKXDQGCyaaJo4mgeAEEPM667sd59/dyoQpUYDUQBCpZiqqmrNIgCEIKlgWS1OTl4OYl9gRoo40VgrRhGpP0G9qMZgFieTKgaKOFXQgolaCE7MBOrgnEO0aKWfLI7rWRaAnC4ATv3ZpiLiVQFYoCmzLAuhHI5eMsInIBkNUXTZUAERAVlvFSrziZoZFxOaaK3HAJOw1K9ArQXKMl/MJ7Ld6Z0l/1m86qMCGEXEe7+EW0+g4iFljCHxLQGcWq0NUp/Ur52K+Vc3ohrrFrs8PzhlJgBiKt7MYoxVKIpiIRudtdc9QSxheTPnHIAYCaNzTlXNzKg+YWRQpgKQRjGIB8Pyb0BJnv1ikFoYOwBEBKAEqFQlaRalFtqkc440n3IZrNp7Z4LExMpgy4SAVBaFVp9zhBCIaBQnDqhPSQgKIAJPksal+AG8ogpRnQCIUVRFoSEE9QIaLNCpqiPFQUK0/wPxadi/ncvxsAAAACV0RVh0ZGF0ZTpjcmVhdGUAMjAxMS0wMi0yOFQwMjo1NTowMiswMTowMGbLlncAAAAldEVYdGRhdGU6bW9kaWZ5ADIwMTEtMDItMjhUMDI6NTU6MDIrMDE6MDAXli7LAAAAEXRFWHRqcGVnOmNvbG9yc3BhY2UAMix1VZ8AAAAgdEVYdGpwZWc6c2FtcGxpbmctZmFjdG9yADF4MSwxeDEsMXgx6ZX8cAAAAABJRU5ErkJggg==</binary></FictionBook> +<FictionBook xmlns="http://www.gribuser.ru/xml/fictionbook/2.0" xmlns:l="http://www.w3.org/1999/xlink"><description><title-info><genre>unrecognised</genre></title-info><document-info><program-used>pandoc</program-used></document-info></description><body><title><p /></title><section><image l:href="#image1" l:type="imageType" alt="This image was embedded using data URI scheme" /><p>This image was embedded using data URI scheme</p></section></body><binary id="image1" content-type="image/png">iVBORw0KGgoAAAANSUhEUgAAADAAAAAgCAIAAADbtmxLAAABmGlDQ1BpY2MAAHjapdG/axMBGMbxTy4tldJSwSAiHW4ootKCqIOrVShIkRIrJNUluUvaQi4Nd1dEXAQHF4cOXVRcLOLirJv4BygIggqCi7sUBRcpcbiDgtBBfOGF5/315eV9qR7qRUk2EpL087S+MB82mivh2BeBcUcddrwVZYOLS0uLDrRfH1Xgw1wvSjL/ZpNxJ4uohFiKBmlOZYC7t/JBTmUXtWitFROMYDZtNFcIzqDWLvRl1FYL3UAtXa5fIughXC30A4TtQr9AGK2lCcFbzMRJPybYxWScxDFVGE16m1G5ZwUTnf71aziPaXUsYB4h2tjEOnrIMVfG/QJyAC/GtKvYKFlRqQe4jbTkrGKtZM+WvZvI0CnjbtnfKb1XMtBoroR//yzrnjtbbDRxhdFvw+HP04w9Zu/+cPj76XC4t0P1M2+29+c3trnwnerWfm7mCVP3ePl6P9d+xqstjn0dtNIWitMG3S4/njPZ5Mh7xm/8b734Z1m384nlOyy+4+EjTnSZunkyzsP1ft5J+63eKWT1hXn4AzDofghlJQBJAAAACXBIWXMAAAsSAAALEgHS3X78AAACInpUWHRSYXcgcHJvZmlsZSB0eXBlIGV4aWYAAHjahVRJtiQhCNx7ijpCMIhyHNPU9/oGffxeaNY3p/5VC5IAQkAhtL9/evh8Pp+PiwaNKZubAYDuugNcMH4ZIAN6A6ATo68kdAA8VQ1DkoEIq2EILiBiALIQDTISWvz3SSQNJHwnilWTGgC/ZMSa1Fc8TDznZH4rgWOtRrwQKGh8VyNZ8bAY9Ccj1EGXUI0JwNE3n3itxrzis7Sq1TgBiNMwesKo1TjfcdZqXBaiWRpLrcbbEjBLU63G9QGv1bit+CSKWi2W8+3QLDluF/wIBgBEaNQWNSjFzHj7/zgOP92EBap3v2BqlNi2pEbGVi0yBNwkcRPiTVxIJDVLRgJxEXGLRgAgLBASkiIIwlIEYgyBJCnC4lKExN6yGSW6SD961nvvQaxhBZq4rbptbX1HlJPSokN37t9m9957a5utDux7Xwk06WnWWOJ2yqgkPqW4e2urnmNPK0HMtq0Hkkc7ZbSXUleHiNMIoGy7r/ppEwAIV+Amv1rS/3ghgCz23ns+m/HrASdJMWT2chsBiS2z73fcLGd+3E8hZ05nQ81zzOW2n8Saj1VzwTMHZ+g6xcPg5ozLASM7Z/hl9kaPnPFQmrcyvm8lFKbrAQwAoegtYFy34rEXRSFP/qEo4tmQ0wywlwPyG5G/BJQXvF5wOR4k7m9HjlupR/y6Mp42RjhWxm+Oh99BvMrwD3UCiGvkpxuRAAAACXZwQWcAAAAwAAAAIACELJ4GAAALGklEQVRYw11YW48dV1b+1tq7qs6t+/TldPsSx3bbcRwncWY0A4LMCOYFXpgHJCR4QvwAnpAQj/wB/gR/ACR4QUKDECMUEjLOZew4zsRxuu122+52n9Pnfuqy9/p4qNNtD1tLpVKpap/vrMu31rdl/nAgIjSpF0kAJAEHGJwAAIQheqeARVqomCQZGUkjSYLmTAyAkCJiESRVNYQAaL3h8k3SzPj6MjEzsr7SqyoAcRABQItRVZ14kqifmNEkTZNiUZiZ934xm4WE3mva8GYGAA5UJ8YYIyCipiKk1ZuTBAhQBGZQFRKvTAgBaQBIeOekBqpa+0gBxFgAlmhqhixJzUKMRVEUx/3RWmel3z9xzrVX2+tuRb3WnrDKVFUEgKlCVWI055WMZ76AieipX0AYzYwQUZqZqJD0tKCqFJAxhKiqSZKooirj06fPMt/odlezhngFYar+0e7jxWLR6/Vc7ubzpNnM4BlDSDLvvQ8hnAYFIlCFRUDEjASgIGFGEcBIoSrMCFAVhgiKTxJPkgJVSeBBhKqaTCb5Ip4cD/efPP/g9q2soSvdTp7nAuv2Vk/2BoHFyWgRYxVjbDezRiMDMicNxqCqqhIZVZxZVK3zaRkgXYaMdeDMoMoapSpo8GSE1t6ihaCqPs3WV/VwPpxOp8fHRw++cUmq7XYzSbLV1W5vu3fw7Emn0xwcD+ZzF8vKQtlI09R7J6SXOldgEDEwAmdguMyYV/lEVWEkARExEkoVBxHWxeUSFefK6fTJ48dlme/sXN7a3vjVnf8NIQ6Hk1ajOZ+Nf/3ZZ9Uij0V+fedqM0v2nz5ut7LtCz1GC2WVJqmry1KgZKLqlbo0qLPanJrAVKgSRX/LPElxQF0smiDy6Ojo7pd3qXLjxo2r1y8fnwxORpN8Nt/u9fLF5OTFcRVKDWE0HJZF2O71IsOzZ0+e7D3tdDo7168miU9SJ6IhBIGD2KuKMpHaPwoFXkXq9Aak+/u//TsFRCEgEAljjFtbW+UiHPb765sbJ8M+Y9HtdAbDgWs0pSge7O1u9Tar+Xwwmy0m03I0XpgbjydZlk2n43armaVOJIqQDEIIIKBABK/iBYuAnT4HwJrx1CkhRosAIRBBo93ImunO25dv/eBmb231+rUrRTH/we1ba+udhw/uSoZGOzt38Vx/1D85folYLhazqpg3mj5ruNWVTqPhxcEsAOa8ihJiAhMEQVChCgXmhKcWT41O6IGq5kCjqPOTk9F4PF7rrlvKRtQHjx/d2Lk+mgy+evrwhzs3Xuzv0tmbb5z79LNPzm9utdorEoNkzPPx+x+812o10tR7DyCqUwCMQUUIUqm2JOolbb/GjmbwoDGS9GZBnYM4IS0E5+TChS1Nk7Z28uPhW29euvPRf2fN1pdffNE1vXnzxsGgf/B036duvbce5tXG2uZkfnL79q3t8+sA4Rws0CJIAOI8LADUusLqeC0rTl4RJgyg1Fe+fB7yUrxTQoRWVoExbWTjl6P5fD7dO6yIF4P+bDK/92T3hzffLWGffPq5c7K1uf7hj3+PrLqbqxffuDQc9VdWVtY31846l1CFqJlalk8gr/UxAIzLLrZkbVK5WHgHhFIYmS+K6ZhFkY/Hi/5gPOhLUzvnu73L59KVxjyffXH314vFIsbYaTXeuXFtcHx4sPd9S+3l84PMwTsyBrMgQhUIgrEUREWUU4O8uhcLdW45BsWpiVRgoSyYTxYn/ee7e9/f/2Z8eOwYm8pko4EktDvpzOZXL5z3Dd3b2/vi/r1G0795cat//GxrvWPTaW+lvdVdXUkTCaVagAUrF6wKVSAGxIAQJEZYiVjSSrBSq4SVWCFWKINYpQzK4FHmhqjOgbF/+Hx0dJyXtv/46ZuXtrrd1V6ruRhNJqPZlfbq5999/Dt/+LNf/tf/nEyH585t73338OrVS3E8Pnl+MJnOi7i4fG1no7cJ79Sh7vPISwCwZYCERN3TjQCFZFxGE3FJV97iXCGIKBZlcyV799zbIdhsNnvyaP/x3r6Z+Tx02i6Kv/7WO8bFX/3ZT37xyZ2yf9Ta2n73vZ1vf/Xlv338+R/97MOVjc63X99fbXduvfuONBJTAlDxiBGAWKQZSVn2BZ4lDYwAlDQzkF7LEmYQyUSTdkvTzNuiZLz25vlOt3N0cPTwxcH7W2/9+NbN0Uef3Pvs6w/+9KcraePb3+z+6NKF+cHLvvN/89d/2SQsTSdr3clwMh0M1nvr0ki4yI0iQgBSu8dYOwxm4BIEyTrTEY1mHrNpZD3KiMIhlLEokljKWueyytsX3ji/2rqzuzt4Obh95eLd3+ztf7Xv1e2sp8OXw73h8Od//FNNtIh5Rqx322tZWoWimo1c7hQi4mgBxtPpA3VBkXQ0M8BOh5VoS3D8j3+CACqsR4EYzUyIalqaCqCxyIsB/uFf//lPfv93R/2jf/z4m0Zmf/6j977af/wXH/7B6ubK+dVV2+g6D0Yzg4OoA0kRrYoiEXcarFfzq7IueJKsYZktAXl7MRURiARakiQ08xAACHCGybj/i3v3ZoNyDa3/vPPg59cuf/fi4GKjPRmH99cuHT5+Ouv3ipV5b2ve2lxRdfPJLMa4ttKxEEl68ZH52bh4xkDhbLI2OYNiBpL+cHfmnKvfq2nf+eWXi2L+6PgQh42nk+GVc1uf7h9+f1T8ZOftXz76flu7L07Gs7FttCYvknH74PiDt24kjWa/PyvLElupJ2OMZFXBROS3hnoz8sxBS9+YYemhrw9L55xCFCYSalgR7Ehy/+DFnChC0kq3m37j9nr2L7uPnrw8UBb//t2emGsnybW8OW9M3uhc+fbprNWW0Qwh6MwKAQGEEIhlpccYSVLl/wkPM4unqEj6+7MyUZeIpj6pRxOJjDGO5qNpbNLsWTiSyt/dex5mR1Ui+9Phxe72w+moI1mmViSbG7xQNNpHlrhKBnkkcbIwi5WZGegpgMYYq6oCoKoiamZAfB1TWCoq+o/2DxzEiU/TNHXeBCGEqqqKGKGIDPOFTedDY8x8M5HEIRlXi5D7TtrsVpv5cDbZyB69eL7a6IjIfD6NNBHJy1A3tcRJCOV4Nmq1OiqZUgFznonzZVWIECoqXjWpijJGevVipFkZqipYKt6JE1XXjj5tJHk+n41jptrtrifqptNpq9WaTMcqyXon9VlqxHgyi5GjWa6qeZ5DJcsyM6OomVm04WQwnY3XIGkCQGEhzktjORoN8yp3zqVpI0lSUNXB59OhiChE1RdaSK0XSTNqoSSbmQe8F8Bi4jRN00WRr3TY7jSzJAEAQZIkCBUQo1aqmtSTHmJkrGApQtu7lodKKXDQGCyaaJo4mgeAEEPM667sd59/dyoQpUYDUQBCpZiqqmrNIgCEIKlgWS1OTl4OYl9gRoo40VgrRhGpP0G9qMZgFieTKgaKOFXQgolaCE7MBOrgnEO0aKWfLI7rWRaAnC4ATv3ZpiLiVQFYoCmzLAuhHI5eMsInIBkNUXTZUAERAVlvFSrziZoZFxOaaK3HAJOw1K9ArQXKMl/MJ7Ld6Z0l/1m86qMCGEXEe7+EW0+g4iFljCHxLQGcWq0NUp/Ur52K+Vc3ohrrFrs8PzhlJgBiKt7MYoxVKIpiIRudtdc9QSxheTPnHIAYCaNzTlXNzKg+YWRQpgKQRjGIB8Pyb0BJnv1ikFoYOwBEBKAEqFQlaRalFtqkc440n3IZrNp7Z4LExMpgy4SAVBaFVp9zhBCIaBQnDqhPSQgKIAJPksal+AG8ogpRnQCIUVRFoSEE9QIaLNCpqiPFQUK0/wPxadi/ncvxsAAAACV0RVh0ZGF0ZTpjcmVhdGUAMjAxMS0wMi0yOFQwMjo1NTowMiswMTowMGbLlncAAAAldEVYdGRhdGU6bW9kaWZ5ADIwMTEtMDItMjhUMDI6NTU6MDIrMDE6MDAXli7LAAAAEXRFWHRqcGVnOmNvbG9yc3BhY2UAMix1VZ8AAAAgdEVYdGpwZWc6c2FtcGxpbmctZmFjdG9yADF4MSwxeDEsMXgx6ZX8cAAAAABJRU5ErkJggg==</binary></FictionBook> diff --git a/test/mediawiki-reader.native b/test/mediawiki-reader.native index 9b0a61b4d..9b35bd7ee 100644 --- a/test/mediawiki-reader.native +++ b/test/mediawiki-reader.native @@ -290,57 +290,83 @@ Pandoc ( "Page#with_anchor" , "wikilink" ) ] , Header 2 ( "images" , [] , [] ) [ Str "images" ] - , Para - [ Image - ( "" , [] , [] ) - [ Str "caption" ] - ( "example.jpg" , "fig:caption" ) + , Figure + ( "" , [] , [] ) + (Caption Nothing [ Plain [ Str "caption" ] ]) + [ Plain + [ Image ( "" , [] , [] ) [] ( "example.jpg" , "caption" ) ] ] - , Para - [ Image - ( "" , [] , [] ) - [ Str "the" - , Space - , Emph [ Str "caption" ] - , Space - , Str "with" - , Space - , Link + , Figure + ( "" , [] , [] ) + (Caption + Nothing + [ Plain + [ Str "the" + , Space + , Emph [ Str "caption" ] + , Space + , Str "with" + , Space + , Link + ( "" , [] , [] ) + [ Str "external" , Space , Str "link" ] + ( "http://google.com" , "" ) + ] + ]) + [ Plain + [ Image ( "" , [] , [] ) - [ Str "external" , Space , Str "link" ] - ( "http://google.com" , "" ) + [] + ( "example.jpg" , "the caption with external link" ) ] - ( "example.jpg" , "fig:the caption with external link" ) ] - , Para - [ Image - ( "" , [] , [ ( "width" , "30" ) , ( "height" , "40" ) ] ) - [ Str "caption" ] - ( "example.jpg" , "fig:caption" ) + , Figure + ( "" , [] , [] ) + (Caption Nothing [ Plain [ Str "caption" ] ]) + [ Plain + [ Image + ( "" , [] , [ ( "width" , "30" ) , ( "height" , "40" ) ] ) + [] + ( "example.jpg" , "caption" ) + ] ] - , Para - [ Image - ( "" , [] , [ ( "width" , "30" ) ] ) - [ Str "caption" ] - ( "example.jpg" , "fig:caption" ) + , Figure + ( "" , [] , [] ) + (Caption Nothing [ Plain [ Str "caption" ] ]) + [ Plain + [ Image + ( "" , [] , [ ( "width" , "30" ) ] ) + [] + ( "example.jpg" , "caption" ) + ] ] - , Para - [ Image - ( "" , [] , [ ( "width" , "30" ) ] ) - [ Str "caption" ] - ( "example.jpg" , "fig:caption" ) + , Figure + ( "" , [] , [] ) + (Caption Nothing [ Plain [ Str "caption" ] ]) + [ Plain + [ Image + ( "" , [] , [ ( "width" , "30" ) ] ) + [] + ( "example.jpg" , "caption" ) + ] ] - , Para - [ Image - ( "" , [] , [] ) - [ Str "example.jpg" ] - ( "example.jpg" , "fig:example.jpg" ) + , Figure + ( "" , [] , [] ) + (Caption Nothing [ Plain [ Str "example.jpg" ] ]) + [ Plain + [ Image + ( "" , [] , [] ) [] ( "example.jpg" , "example.jpg" ) + ] ] - , Para - [ Image - ( "" , [] , [] ) - [ Str "example_es.jpg" ] - ( "example_es.jpg" , "fig:example_es.jpg" ) + , Figure + ( "" , [] , [] ) + (Caption Nothing [ Plain [ Str "example_es.jpg" ] ]) + [ Plain + [ Image + ( "" , [] , [] ) + [] + ( "example_es.jpg" , "example_es.jpg" ) + ] ] , Header 2 ( "lists" , [] , [] ) [ Str "lists" ] , BulletList diff --git a/test/tables.texinfo b/test/tables.texinfo index 4f09246af..3b284e36c 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/testsuite.native b/test/testsuite.native index 5f9be452f..bebbde64a 100644 --- a/test/testsuite.native +++ b/test/testsuite.native @@ -1906,11 +1906,15 @@ Pandoc , Space , Str "(1902):" ] - , Para - [ Image - ( "" , [] , [] ) - [ Str "lalune" ] - ( "lalune.jpg" , "fig:Voyage dans la Lune" ) + , Figure + ( "" , [] , [] ) + (Caption Nothing [ Plain [ Str "lalune" ] ]) + [ Plain + [ Image + ( "" , [] , [] ) + [ Str "lalune" ] + ( "lalune.jpg" , "Voyage dans la Lune" ) + ] ] , Para [ Str "Here" diff --git a/test/writer.asciidoc b/test/writer.asciidoc index f5fce08f7..1b7ad54e3 100644 --- a/test/writer.asciidoc +++ b/test/writer.asciidoc @@ -622,6 +622,7 @@ or here: <http://example.com/> From ``Voyage dans la Lune'' by Georges Melies (1902): +.lalune image::lalune.jpg[lalune,title="Voyage dans la Lune"] Here is a movie image:movie.jpg[movie] icon. diff --git a/test/writer.asciidoctor b/test/writer.asciidoctor index 21ec18ec6..0b238ef2a 100644 --- a/test/writer.asciidoctor +++ b/test/writer.asciidoctor @@ -623,6 +623,7 @@ or here: <http://example.com/> From "`Voyage dans la Lune`" by Georges Melies (1902): +.lalune image::lalune.jpg[lalune,title="Voyage dans la Lune"] Here is a movie image:movie.jpg[movie] icon. diff --git a/test/writer.context b/test/writer.context index 540bbce24..1ee01e91e 100644 --- a/test/writer.context +++ b/test/writer.context @@ -930,7 +930,9 @@ or here: <http://example.com/> From \quotation{Voyage dans la Lune} by Georges Melies (1902): -\placefigure{lalune}{\externalfigure[lalune.jpg]} +\startplacefigure[title={lalune}] +{\externalfigure[lalune.jpg]} +\stopplacefigure Here is a movie {\externalfigure[movie.jpg]} icon. diff --git a/test/writer.dokuwiki b/test/writer.dokuwiki index 8f8124db7..bb47524f3 100644 --- a/test/writer.dokuwiki +++ b/test/writer.dokuwiki @@ -619,7 +619,9 @@ or here: <http://example.com/> From “Voyage dans la Lune” by Georges Melies (1902): -{{lalune.jpg|Voyage dans la Lune lalune}} +{{lalune.jpg|Voyage dans la Lune}} +lalune + Here is a movie {{movie.jpg|movie}} icon. diff --git a/test/writer.haddock b/test/writer.haddock index 81865b2e8..e580ed168 100644 --- a/test/writer.haddock +++ b/test/writer.haddock @@ -614,6 +614,7 @@ ________________________________________________________________________________ From “Voyage dans la Lune” by Georges Melies (1902): <<lalune.jpg lalune>> +lalune Here is a movie <<movie.jpg movie>> icon. diff --git a/test/writer.html4 b/test/writer.html4 index e2c6cb3a7..d5e57b19b 100644 --- a/test/writer.html4 +++ b/test/writer.html4 @@ -708,9 +708,9 @@ class="uri">http://example.com/</a></p> <hr /> <h1 id="images">Images</h1> <p>From “Voyage dans la Lune” by Georges Melies (1902):</p> -<div class="figure"> -<img src="lalune.jpg" title="Voyage dans la Lune" alt="" /> -<p class="caption">lalune</p> +<div class="float"> +<img src="lalune.jpg" title="Voyage dans la Lune" alt="lalune" /> +<div class="figcaption">lalune</div> </div> <p>Here is a movie <img src="movie.jpg" alt="movie" /> icon.</p> <hr /> diff --git a/test/writer.jira b/test/writer.jira index 268abb0d9..920354662 100644 --- a/test/writer.jira +++ b/test/writer.jira @@ -502,7 +502,7 @@ or here: <http://example.com/>{noformat} h1. {anchor:images}Images From "Voyage dans la Lune" by Georges Melies \(1902): -!lalune.jpg|title=fig:Voyage dans la Lune, alt=lalune! +!lalune.jpg|title=Voyage dans la Lune, alt=lalune! Here is a movie !movie.jpg|alt=movie! icon. diff --git a/test/writer.man b/test/writer.man index c476c35aa..fb21c9f60 100644 --- a/test/writer.man +++ b/test/writer.man @@ -714,8 +714,8 @@ or here: <http://example.com/> .SH Images .PP From \[lq]Voyage dans la Lune\[rq] by Georges Melies (1902): -.PP [IMAGE: lalune] +lalune .PP Here is a movie [IMAGE: movie] icon. .PP diff --git a/test/writer.markua b/test/writer.markua index bc9668a06..a7032dc27 100644 --- a/test/writer.markua +++ b/test/writer.markua @@ -656,6 +656,8 @@ From "Voyage dans la Lune" by Georges Melies (1902): {alt: "lalune", title: "Voyage dans la Lune"}  +lalune + Here is a movie {alt: "movie"}  diff --git a/test/writer.mediawiki b/test/writer.mediawiki index 23cb78e60..8154bd375 100644 --- a/test/writer.mediawiki +++ b/test/writer.mediawiki @@ -650,8 +650,11 @@ Auto-links should not occur here: <code><http://example.com/></code> From “Voyage dans la Lune” by Georges Melies (1902): -[[File:lalune.jpg|thumb|none|alt=Voyage dans la Lune|lalune]] +<div class="figure"> +[[File:lalune.jpg|lalune]] + +</div> Here is a movie [[File:movie.jpg|movie]] icon. diff --git a/test/writer.ms b/test/writer.ms index fd78272d6..ec7d5d6b1 100644 --- a/test/writer.ms +++ b/test/writer.ms @@ -954,9 +954,8 @@ Images .pdfhref M "images" .LP From \[lq]Voyage dans la Lune\[rq] by Georges Melies (1902): -.PP [IMAGE: lalune] -.PP +.LP Here is a movie [IMAGE: movie] icon. .HLINE .SH 1 diff --git a/test/writer.muse b/test/writer.muse index 2c96f6bf2..3a016ff0b 100644 --- a/test/writer.muse +++ b/test/writer.muse @@ -678,7 +678,7 @@ or here: <http://example.com/> From “Voyage dans la Lune” by Georges Melies (1902): [[lalune.jpg][Voyage dans la Lune]] - +lalune Here is a movie [[movie.jpg][movie]] icon. ---- diff --git a/test/writer.native b/test/writer.native index 15971bfff..649e415c3 100644 --- a/test/writer.native +++ b/test/writer.native @@ -1841,11 +1841,15 @@ Pandoc , Space , Str "(1902):" ] - , Para - [ Image - ( "" , [] , [] ) - [ Str "lalune" ] - ( "lalune.jpg" , "fig:Voyage dans la Lune" ) + , Figure + ( "" , [] , [] ) + (Caption Nothing [ Plain [ Str "lalune" ] ]) + [ Plain + [ Image + ( "" , [] , [] ) + [ Str "lalune" ] + ( "lalune.jpg" , "Voyage dans la Lune" ) + ] ] , Para [ Str "Here" diff --git a/test/writer.opml b/test/writer.opml index 4d2a412f2..5383b4b0a 100644 --- a/test/writer.opml +++ b/test/writer.opml @@ -64,7 +64,7 @@ <outline text="Autolinks" _note="With an ampersand: <http://example.com/?foo=1&bar=2> - In a list? - <http://example.com/> - It should. An e-mail address: <[email protected]> > Blockquoted: <http://example.com/> Auto-links should not occur here: `<http://example.com/>` or here: <http://example.com/> ------------------------------------------------------------------------"> </outline> </outline> -<outline text="Images" _note="From “Voyage dans la Lune” by Georges Melies (1902):  Here is a movie  icon. ------------------------------------------------------------------------"> +<outline text="Images" _note="From “Voyage dans la Lune” by Georges Melies (1902):  lalune Here is a movie  icon. ------------------------------------------------------------------------"> </outline> <outline text="Footnotes" _note="Here is a footnote reference,[1] and another.[2] This should *not* be a footnote reference, because it contains a space.\[^my note\] Here is an inline note.[3] > Notes can go in quotes.[4] 1. And in list items.[5] This paragraph should not be part of the note, as it is not indented. [1] Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document. [2] Here’s the long note. This one contains multiple blocks. Subsequent blocks are indented to show that they belong to the footnote (as with list items). { <code> } If you want, you can indent every line, but you can also be lazy and just indent the first line of each block. [3] This is *easier* to type. Inline notes may contain [links](http://google.com) and `]` verbatim characters, as well as \[bracketed text\]. [4] In quote. [5] In list."> </outline> diff --git a/test/writer.rtf b/test/writer.rtf index ab1e00c21..f3cf5fdce 100644 --- a/test/writer.rtf +++ b/test/writer.rtf @@ -421,7 +421,8 @@ http://example.com/ {\pard \qc \f0 \sa180 \li0 \fi0 \emdash\emdash\emdash\emdash\emdash\par} {\pard \ql \f0 \sa180 \li0 \fi0 \outlinelevel0 \b \fs36 Images\par} {\pard \ql \f0 \sa180 \li0 \fi0 From \u8220"Voyage dans la Lune\u8221" by Georges Melies (1902):\par} -{\pard \ql \f0 \sa180 \li0 \fi0 {\pict\jpegblip\picw250\pich250\picwgoal3000\pichgoal3000 ffd8ffe000104a46494600010101007800780000ffdb00430006040506050406060506070706080a100a0a09090a140e0f0c1017141818171416161a1d251f1a1b231c1616202c20232627292a29191f2d302d283025282928ffdb0043010707070a080a130a0a13281a161a2828282828282828282828282828282828282828282828282828282828282828282828282828282828282828282828282828ffc000110800fa00fa03011100021101031101ffc4001c0000000701010000000000000000000000010203040506070008ffc4003e100002010303020404040502050500030001020300041105122106311322415107617181143291a1234252b1c115f016336272d1082443e1f1265382ffc40017010101010100000000000000000000000000010204ffc4001b11010101010003010000000000000000000001110212213141ffda000c03010002110311003f00dadd18a10a704f6a95ccc57e37750782b0d8d9ea0cd32e7c5446e07e9f4ad723119a7b89e61e348f260719278aad613cbb640002938c76a182b264fc87bd13009c0c019c76e3d68a072e1cf6f4cd502d330c28269a61bb39c923923d4fad44c08dccb95cfd28b8280769ee08a263891e1808739e4f1d8d149392172cc714050dbb9fde8960ed8c60b79b1ed44103b05c331dbdb1dc5026ac1946d20ff8140aa631c773ec738a0346a003bf93e9cf02801895e7b9a01886796c923bd0090a06393c76a0142003ce3d86680d8dd9392303f5341ccc1b3cf7a2c812c37e4923d381429757013209fa511c18146c9247a0f6a007900c0c671c6280854e086c673eb45c27c038fd68aedff2fda836ef881f136f25d5e6b7d1262964aa02b03f98fbf153131935edcc97576f35c33349212cc4f39f7ab26186dfce5b200f73451f7600dcb8cf27e7400c0b291914046c9e0718fde81371b8e7273f4ef4007691919240e714097f31f376e7b5008caee27807b0f5a02c8e1b3c6d27d33cd0201d839523144d1a149ae084b78da47638211771fd050d582c3a0faab5119b6d12f8ab1c06788a0fd4e2ac356fd1fe08754ddccaba849696309e598c9e2103fed1dcfdeadc44fea5ff00a7f956366d375e492403ca935bedcf1eea4ff6ac68a55efc1beb3b552574f8e7009ff933a927ec715bc82b3a8f4d6bba5ca1352d22fe061cf9a0383f71dea5119cc6c0baed3eaac0f1fad40897dcc3d81f7a052366c1007df3400f21edefc5008c28f30c9c5170ee4fc37830086395250a7c66770c18e78da31c0c63de8609b41f7c515c5172a30c3b76344a3e377cb2339cf7a242aea89808cce368272b8c1a2e107c672a49f5c1a181c9c7ae7da8a2119e7b1f5068099ffa68258a132062d8f9e0f34059502b61bf2824e681bb297ced2a71efda80f19c47b9c77fdbe74057c13e539cf3c1a0eeeb9c73f33405ddb4f18249c1e28062b79ae242902024465b9214614649e7bd0362a7249eddc513456e5720f38f5a1a98e96e95d6baa6ebc2d1ad1e65521649bb469f563534d6d7d31f04347d2a2fc5f535db6a0e83718906c887cbbe5a9a8bef44dce9f731ca9a2e89169d6d6f2184b1455dc07b11dcfeb4d16f119c649a681285b03d3e5500f87820ff006a0e098191de80ac9b8904647b55d11da9681a56a31f87a869f6970b8ffe4883629a289aefc16e92d441682da5b098f21ed9f033f353914d19b751fc08d66cc16d12fe2bf45ec92ff0df1fdbfb559ec667aff4eeb1a04db359d3ae6d40eccebe53f46ec7f5ab82263da7dcf3eb5174e5181076918c7de869503232491ee4515c1803824f03b51287f30e0e7d803449494832c157278a2e8c71fcb9f9d144639236824d01e142efb1768cfb9c7ef40512a818de78ff00a682518e7cc30ab9e00a02cce9953247bd41e467191ed9a04205ee99da4e4e3d283a524b0427b5026c18a8e082067db8341ce0e39ed409b6502907391edda80f2dfdc496f0c124ac6184b144cf0a4e338fd2894f7a7342d4ba9b568f4fd261f12571966270a8bfd47d8511bae85f02b47b7fc34bac5d5c5dc88a0c90ab6c8d9bedce3ef4d1ad691a6dae976a96d616d15b409f9638d70054a1dbc68ea51d4329f4619a8022b78e04548515117b05000a035c5c4702a995c26e3819f534047bcb68a458cce866719540724d02e41c0f7a012a40f6141cbc8e7bd01719e38e6838af1c0a04ca8206d3cd037bdb082fad9e0bd8a39e0718649141047d0d5d18f759fc0cd3af164b8e9999acae4e4f81236e898f7c0f55fed574615aee83a96817ef67abda3db4ebdb7f66f983d88a061bb8db9e3d45165076db83c1f950a53780d8247c80a2398f182724f1c7ad080c608cfa7a51a0062adc7afbd0130173bb9c5070f071cb37e82826106e8f615e01c9e680d6b35bc534be3c1e3831b2aa962bb188f2b71df1de819ae4b1048c7f57bd01a58268e332642ae0704f7cf6207af6a01b99e17b7b6416e227407c494139909ed9f4c0a04a4e501e0f1eb40d263e53dce7fa682c9d0bd13abf58dd6db18bc2b157c4975270ab8ef8f563f21447a73a03a1f4de8eb031582b497328066b97fcd21ff038edfde88b7e32703bd64188e7e6283864b73400cd804b67ca3268317eacea6d56ff005233592f8b6303f953fa4af7c2fa93417fe98b763e0ea171297bab98558068f695ce0e08fdbd281e5c6a57ba5e9d14d716ef7774f2ec112601da4f27ec2827ada74bab559a20e148fcae36b0f91140283729c77a0e0a7777a01dac68395719e39a029607cb901b19c501480ab9279f4a086ea8d0b48d76c0586b7143224a76c61ce1831fe93e86b43cd1f12fe19ea7d2533dcdbeebcd20b612651e68f9ece3fcf6fa5067cbcf20ff009a051724905411e94032799060723da8406d6c67e7ea68d0e1770fe5cfb5026c37039ef9a02eca098c91e6e01e71c500b1d8a49c12786cf6a06a4e256008e3d050119958007920e2801154e32fb4120927b014017eb1c523ac5209a356215c291b87be28957ef853f0d66eaa99352d515e1d190f947669ce7b0ffa7e74a8f4be996569a5d9c56b6704705b46bb5238d42851f2ac875712bc70b3c30f892019540704d01ad2669a0491936330c95ce7140b2e4939a03638c7e8680ae485e33bbe540d60d3ada162c90a02c7270a39340a4f28b68da4645007a8f6a069a746f73235ddcefc391e12b2e1916824948742c99382473c73404791c617695279dc0640f9502c578c9efeb4095cb4cb0830ba21cf999c6401f4f5a05061d430c8079a02e03b3004311c7d281b5e3cd676c65489ee594e4aafe6c7ae07a9a0a075bbea3a8ea96f047d3935ebc404f04ad29411e08e011d98fed416fd212ee5b05b4d5ad6300c615807f1171eaa49eff5ad418c7c55f8466dd66d57a521f20cbcd66a7247a9283dbe5418a63862479877cf1f6c5008e400bdf1ce684016fe53dfbd1a73794600e08ce3d6800377c8c7d6800a9cf75fd4503d91492460f7ee3d28247a7b459f5fd592d22711c206f9e563858a31f99cfd050583518ba75247b1d134f9aed21396d4669769931dc01c003f7a329c4d17458ac5b55d36c12e040a3f1da75c1cb04ede2447f7f6a94567ad7a66db4fbbb29ba7d65b8b4bd8ccd09c8231eaa07b8ab04a7c2cf87b3f53ea8d77abc72c1a5dabe2452bb5a561fc83e5ee7e541e988218ed2dd22b7855228d76a46a00000ec00a510bd4dd511f4fe84da95cc31f880022da4902b1e7d3e99ac86fd03d631f565b4ee6d4dbbc649009cab2e48c83f514165b8b94b6895c44f279c280839e78ce28178ae6de46748a789e453865570483ec6812d42e85a421fc37918b00a883924d024c6e99b7a2a966c0009e17dc9f9fed40f81c77e28139218e4ff9815b9cf23340a01c907b9140201038ed402fcafd28386464e4fd33c50272bc60032609cf00fbd024f722dc66f24822ddf972f8feff00e280f69b24844919cac9ce7de83a447f30ded823007b50459d6ecacb528349b979127651b1dc795f1f3f7a0990148054823dc5015d491c0a0c3be337c2ff00c489b5ee9c87172016b9b541c49ff5a8f7f71eb560c1fc43e0a47e1aa94277310431f91fa551c1727f29ed409b641c86e31839a3454805739c1f6a026f1fd740f64665fc8c31cfde82db79bb40e9e8f49b62eb7d7e8b717ec832c91ff247fa1dc7df2281bcc9369d671493c422b7911654c1215f92bb8827bf068624ba635392df5eb4b9924558ee5bc19b71cee43c6dc7cf34c657be8db0b0b9d0f51d2afe668934dbf9628ddb8c2b8c0073f3a80da37546a7d25174fd95dc125c69f7313ee5655dfc313bd483cf07b1f6a68d5b48d5ec758b612e9d7293211c8fe653f35ee2a084eb9e8bb1eafb3582fe496278f3e1c919fcb9f97ad03ee8dd017a6741b6d3229dae161057c5750a48249ec3eb4139238568f6a9e7b103b5037934cb3793c610a2cd9277a8da73f5140ee38f6280c4b11c65b934023006d50050030e4647de80c846de3b500fcf9fbd0197273ed4007b91400e580c8e45074a82400e72682b36fd2162b7f25ddc09af2766ceeb872db79cf00f6a0b3229550140e07007a50092db860673de818df473c862686dad6470d9cce3b7b63e740fa1de6252ebb5bd81cd00bee2d800d003a6464004763ce683ce9f1cbe1f1d3a67ea1d1a30b68edffba814708c7f9c63d0fafceaca31e6dc71e1f07daa82608c83819f7a1a11ce149238fd68d0a579ec682cfd27a7c3a86bd10bc38b3b756b8b93c1fe1a8c91f7381f7a034f752ea5aa5c5eb292f732128037619c018f6ec282e5a2cb047abda74d5ce9b6da80f136de4a496219b3e48c92000323ea73467519d3da5bb757dbda410ac90c77c23058f99007ee7ec31416882ee47d23acb5185caf8bab4691b1efe57fff0038a9457ee75a82f6e7429350466b482f2742c0f74241c80c38c64541a9cfa1e89ac0177d33ab3d8de28f2b5bca429f91140e2c7a9b5ae9fb85b6ea9b46b9b3c796fe040768f76ec0fafb1f9505df4ebdb3d4edd6e74db98ee216fe68ce47d280648f75e2485a44da385ddc13f4a025ddbdbea16a633286566ce55f9c8f6c502ad750db2c514f30dec428247e6340bbf04100b73402afb943ed2b9e30683836defe9403bc1e06734020e06280cafe8683a375941d841c77c1a0151b467b50159f00e4127e5402872371040c5046eb5aadbe9b1c02e2f6dad25b89047099c677b7b0140fe3f1010afc803f3018e68160c3041ee2823f5dba92d34db89a1d9e2843b03b6d05bd013560c1748d57aa2797c6b35bab78e6959dc47231580ff336dcfb03c1a58364b5bbb7d7fa7b7427f1f673830c8664285bd1815238fad20f2c7c41e979ba43aa2e2c1cb1b663bede438f3a13c7dc76fb5515e9065b851f7a02950002a09c51a1b83cf14176e90d3645e9ad7752752aac23b3439c066665c827e944d29a6410aea725c4567135bd840d3c88a723728c29c9efe6c50d3ee9545b0bf8ef2e6e3c2fc2c6f72f2920e5f19039ee4938a9a875d03278377acf52ddf867f036ef71923932bfe51fbd3475cdc369df0db4fb389d4ea37970fa9cc0b00511795ce7d4f181eb4cd2451755fc45ac16d637381b14ca36b641dfce723e4053170d6cb52bbb362f6d3cb19241f2b9029862f09f143549ba7e7d2eef6caf2797c66ee17fdfd69862d1a069da7dfdac579d17adcda5ea9e1a992376c4723e39e3b024fd7e94c458ac3e25dee8d31d3bae74e7b79002bf8b8549471db38f5f4ed4c165e943a06a328d4ba605b4b22a1523c420c64fbaf38a82d36f0ce7cf7463790729b53017e940e0b0ceceed8ce0500e1b70daa08f5c9ed41d271cd0132476e7d7ff00aa069797d2411168ed9a41fcc858211f73c5075acb25ca6fb82aa31e58a36c81f561dcd033d42169e158ac64b98151b3981c2966cf639f4a064c7a8ac55e4865b7d493701e1c8e52403ea3cbfda827e390ca3f2c914aa81991bd281cdacc2747215c60e0ee5c67e940cb51b0b2bcbd824bfb08ee1a252d1caea1821cfa67b1fa504982b2283ce08f518a08abb82f6dd0369a5662081e14ce40c7ae1b04fda82275cb0bfd4f4536f7114589a5412461f3e4ce4e0e060f63f6ab2893d3b4b5b5b78e22ed22aae3cc3cc7e64fad3449a22a461500007602a0cd7e3b74c26b5d2ad79147baf34eccca40e4a7f30ff3f6aba3cd0543267eb5427b86f1f4c76ef45d0eca1ad5ef224d13e1cf4fd9b22192fa67bc955f8c8c617fba9fb510d7a6ed3fd43a735e5b54964be658c048fb6cdd9e7eb8a186bac97d174e6d22e23437b7ac26b95e77c68bf950fa7279e2b22dba45b59e97a669fa4ea36aeff89cea9a90451fc355ff0096ad9f4ce3f41570675d4fa8c77da8de5cde5be26bc653171ca47dc1f6c9fed5562b97f70276808da7c24f0c1c63804e33fa8a2928c0e0383c8f7ed41d92a41393f4a2548595c2c37493db4cd04e8a08f139566edfef3445b6e7aeaf65d2df48ea2b11776ae02a93e564c772adef409f4ee8ba9a21d73a36fa579ad9f325afe599171ed9c30a960d5ba0fe2843abb47a6f510fc26a4c36890f9558fcc6783506a1147b510024e30339ce680d2c6ae9861eb9a009178a0205443b989e39cd01d8075e3047ce80563057ca381ed4011c4531e503d85013c91b804a21279c903341131cda8c3abdc8650f6d20c4321232adec3dc504bab2c113c9293bb1963df3408dd4b75e1efb2856463dbc43b4631fad047e9177ad4fe32ea16b1db4b8fe1aa92571f5f5a0916bc8e0895af5c46c17cd8c9ff7da80f6d736f7f6915c59cab35bc837238ed8a072a31c1ef4062870718a06f7702dc5b3c522ee4752ae0fa8230683c75d6ba3b74ef535fe984929149e4278ca9e47edfdab42058003763ed409f88ffd6dfad06b1f12ae612fa0c76e0b471e9916d23f973eb4158d3efeff004a984da5debc1295d8e4018dbf3145d583a2ad96f356bbd7f5d90dc59587f1e79a6392f28fcaa3ee47159444ea3aa5ddfc7acf50dcdc344d7a4dbc317f52641200f6000fdeb41b5ef51d8eab672ffa9e971c97c11638268e431a46000012a3b9a351567db823b11f3ef40948e428048207a8340ab48ae83cb83ee0f3428a982719edf3e68c9cc97d3fe15ad8c9be138f2bf38e7b8f6ef40f7a5f55bdd3f56b46d3649127f1405f08e7249c76f5fa50689d48ba5f545cdcbdb462cba9206411b2b055bb07d4fb1c73528d4fa8f52d62cf47b6b8d2e65fc458c49f8a818795c151939f977a823ba0fe253750eb7fe937b04293f9f6c90be41dbdc7ff006283473c1efc1a06f69776d73bbf0f2aca32572bc80470450284a46dfca19f819f5a04e799614def26c0bdce09cfd85045dc75769d12dc3c3e2491db0dd3c85195235f7c91cfd066ae0cdba9be31f4ec61a386c1ef9d4ee473e45cfb1cf34c101d3ff1ac9d481d46c628ed24751881880833f988e7b0fa5328dfed2f2def2ce2b9b79925b791772ca87208f7a60182ee2b95cc0c48f53823fbd40ac658b30f4f4a086d4ee1d75bb6b78f4e965596366fc5211b23238008fde81f43692da5bc30d97831a0397dc09e3d714087506bf61a2c4cd77324726d2caaec141f9fd2ae0c435bf8c57173ad7876f7a2daca10489121244cdf319ce3dbf5a834fe81f881a6f57bcb6ba7c53c72c11873e28cee1db391dbef4199ff00ea4348116a5a66a8a8a04aad04847a90723f6ad7d18c312ddc02a3815423ba0f63fa541687bd9efe1b533b3c9e0a78473e899e318a09bd0ba6eef543e3b2bd8e9b10064bd9e4da001dc81401aeeb29a984d0ba7d5e1d06d4e6594f06523bc8e7f5c0ac8af752dfc17d7090d9218ec6d9447129ee71fcc4fb9cd6842ab10dc0014f3e5a2c1704b671dfdc734525226dc939e283a362c7f940344a380393df144733e2276e38f5efcd01b4bbbfc3dda4a9298a44395902e4a9c70682660d4265d62de40b1bdc1545054f95c8fe627df141af7c3af8808f3dd68dd5d2a45765884b8908d8c3b6c27b7a77a945d7a5fa474bd2ba8e4d5748b28624955d5d8b13b79ee9e983d8d40a753758c7a46b96f6114725dc92279a2810b3a64f94900763cfafa503fd3b59b79ed84da34713c0cd890f0a158fa1f981de826e1b548959fc4dc5cee24b6467e59ed4101ff19e9f676baa5d6a72c50adb4ad1ac790ccc076200f7ad41e7df881d79a87576a5f87b0f161d381db1c2a36e7e6d8ff3416bf87ff082c6f208ef7a82f22b9761bd6d619785f6dc477fa53705ab57f83bd297ceb1e9caf67708db9c4526723e849e3e94f212dd25d117fd29a8c09a76b534fa39cf8b6b71ced38e36fb73417f52e64548e34007e673e9f21ef590a1c918c90718dc281a69b68f67118d9da5058b798f6fa7fe280daadd1b2d36eae70710c4d263df0a4d583cc7a668fd4bf11b5837d7c93dcd9a3146959822a0e781f4cfa55161e9dd7fa67a4f55b9e9aea3e9f81fc09ca0ba118998fcdb2338c7b528d39f4cd2ba76e2d357d292df4eb391809963420ce1b1b576fa1e7359119f1eb4e17dd033ca172d6b2a4df303383fdeb5c8f2eef3bce4e0e335684cb0c9f354160d36f64b0baf16072b91b5f03391f43c51aab23a5debe91c4fad4d73689e6fc3a290573ff4f03e59f4a3280d67581ce916567f84b58ce0a1fccec3d58fa9a084de08c90464e4d1a8e419059b201f4a05630a176918efc50176293872c17bf14042aa0125b03db14046c60b60123fde6827fa0c68edd5365ff11346ba6292ee64194240c807e59a32b7fc51bfe8bd5ed5db424860beb62b89218422ce09c11c01dbbd0660ae110bf1bf2154838dbebfefeb41a8f4cdac7f117458f4d9ecd2df53b4cf81a822808c47255c0f7c8e7fb54a2ec2cfabba3b4b4b8d3af12eedad40926b0f070a13f9b633649f7a82eba6ea4357d321d4ecad512daf20df26e016507fa4fbfaf3e98f9d067dd2bd2faac9aa4d72d72d1e9510ca46a7631c7a320e18f1dfd7bd059afb7da816d23de4ba5de211346a1e4785f190548e4648c63b64e6b43ce9d5baafe3b539c5b452dbda46c638a167cb281c73ee4ff9340e3a3fa5f5aea4ba58f4bb57dbfcf2b02a8bf7f7a0de3a5fa0b50d2a2d92eb3e048c0a97c867dbedcf6a944e5cf4f6b76d1b3d8ea42795066266c87c81c65b9cfaf15048e83af3cd64abac08edaf01546c38dae4e0657ee6826e5b892de3702292e2545ddb55700fd0fbfca81c4b3bc718716eef9eeaa402280d14ab3c0b2c65c06fe571823ed40df56b217fa6dd5ab9216689a33f2c8c558307e83b8d77a37aaa7d22f2512c28768800c9954671b3d33ebef568d0ef7a7749eb0b5bbbb162d657b32b46d2e1564c8ed9c5644d1b0b9bbd261d2a440af6cb0e2e5b1e7dbc1238e0f7a0375b696daa7496a3a4dac8a92cf078685b271db04d391e40d5ec4586a1716de2a49e0c8c85d3b120f715ba1899173ff305413070abd89cfe9f5a2d3ee9c8639fa874eb6b804c52dc46b20c9f302c3bd11e84d47e1af4d5dc6521d3e3b662c19a58721ff5a9a321f89bd27a374b456d158dccd34d333332c9b4b2afbe47a7cb1f7aa33d2bc0d8c0f1c8f6a2c14b6d501b39cf63450897380c319e3de8065031c038f7ed40d8faf1ce41e4d004876a8dc3cc7e743025c956c818028c904579e7f0e15695c9c0541924f6c00283d0bf07f42d6b48820b8d62d20b2b58d656404959e52f83c8ff00fcfafbd4a35bb06f12391a48dd55cee2b2f3818ed8f6a8158a159890f02242079147623e631c502b0db436d1ecb7458d4738038fb0a087d6eeb508f48bb7d32d95750752b6c26c905b3ddb6f61eb574794f5cb6b9d0fa9678b512b25d24bbe52b8c1638278fbd582c57ff12afaed45b5bc0d0d8a8c08a2731ee3eec5793f40450466a1d59af446293c186cd53ca0c36eab93dc649e49fbd048e89f1675ed35e301e293919dcbf9867b37cbe94a35fe94ea4d33aba6824306dc48015750d86c6e247b0cf63591a40b8dc23fc30f14138dcac3000f9d03687547f12e8dd5af816b13148dddbcd29039c0f6f6f7a0eb5d62caf5636825db70c9bc4328f0dc0271c8a090627d3073ce681acf6505ccf14d35bc2f2c2731bb28254fb8a075144a83ca806792400334049ee6281e2496408656d880ff0031f61fa50446bd76058ea1b9e21025a3bb48afe71df9c7b71de9c8f196a0de23ca7b827d4f7add117e0cbfd4b5059392369663ff004e71c51aa97e8f555eadd258f2bf8a889cff00dc28cbd0bf123a926e96d163bdb74490bca2321c678209ff001591e71eafd7a7d7ef45cde2c20aae144638033fb9ad2e1b5e69d058da431ccf21d4a5c3b4631b62523807feaf5c7a50222f2d648c25f5aeec8c2cd19dae3d3e87e944d3eb7e90d425b49ef2292de38224f1505c3f8724a9eeaa7bd0d57a60406059436306868a7803839c7ad1a158039c13f4a33a716767f8cb9b6b55e1ae2458813e9938cd07a9f42d0b4de99b4b7d1f41b58ff19b03c93ba06607fa8b1f5f619a5b8266d74a65d42da6ba90cce996dcdc8c9fff006a5a2c2635083b05ef83eb5028076341db4b1ed9f7a04651fc41db18ed419d75b744dbea335fcb0db0335f2057901c05da73c8f9d5d18a75174a3f4c47335e35da4ce418a489374254f707d463d33565d1529b569a489a17944b06ec8057d71dcd037b4b6b8bfba31584124b27e62a8a4f1ea68357f83da7ea5a76bfe0912453ccabb49194653cb60f6ce3dfda983d196cd108c2401711f9768e306b2297d73fc6d02773a8b591922693c5004bb9d72542fa2f6efde8314ff867aeeec27500b77bb5670e36ca19b1dff2e7f2fd2837ce8bd5dd348b78b552219022870d9c46e792a4f6c608a0b846c8e03232b29ec41cd0199f1410fd4b24b1e8f712c0a5e4452d851e6c639dbf3238a0afa42ba77475e4ba8470896681da45180b18da76af3c9029c8f26dc1df2b9c606e273e86b743331924f27f4a82c12280e59b008e79f6a2d4d74188ff00e30d203a82ad7519c1ff00b860d11ba7c5e86c9fa3afae6f4091e043e021270b21e01c7dcd6479ab4dd3aeb56be4b7b184cf2b301b57d07bfd2b4bad0fe25e9f6960ba7c7a55ac50cd750335ccaade7723b83b8f6e38a2207a5ba4e7ea3d93780cb616ca53781f99fbff009a0b675a5be9765d43a75a6ad3b25adb4185429b831c70303dfdfd2831eb8954ca48f3827819c71ed406b2b1b9bf9a5fc1c4ce2253238047957dc9345d122b792eee522811a495ce1157b93ed444ff0049f476b1aaf51c761345269d25be269259570c833c6077249e062a68f53e8ef0da69509d4ae225b92a04af232ab16f98cf1f4a5a266d4dbca8af13a329ecca723f51502d14f0cb9f05d1c8ee01c91f6a0393b4edfe63c8a031608859b38f97340d84d04e5846eae50f9829ce3eb400fb24466041f5e3d2823f56d22db57b192d6e61468a41c823ff0035651916bbf04ada7badda5cad6d1b72c09dc33f2a6875d25f0865d06fe2bc6d4c4d3282026cca8cfafcfd29a34cd234a10c768f711a78f1bb392a3001208e3ec69a26a58d640c832091c90706a084ea1d3eeafdadf4f86da3166c0b4b397c18f046140f5ce4d04f4702436e91c28a9122e028ed8a0a9f5a5b6a09a1bc5a135bc72cce048b3c5bc15c638f9d59043fc2db997481aa69dae49e1cb6bb643239211939e467818f97bd305965ebce9a10bc8da9dbaa2679dd9ce3d8530572cfac87566ab05ae9f1490692b9696e1f833738555f96793504df5f25945d2576b7ec16dc46792381c7b7ad5e60f234980e42f6c9c56a82ec3eff00bd4124e49700f1c646e3cd169ce9575f83d52cee324347323f6e3861ff008a23d47d4ba6a75074fdcd8ef317e2e2ff0098bdd4706a60c3f4ae8cd5f44eb8fc3e97248a638cbc73bf90483d463b373e9574685abf42a6b5649fea72bbdeac4a8d3b018cfae31f7a6895b6b29b41d30d8e9f6bbed9213e1b7a994e724fcbb5064bd7835a9752d3af75d8116354778f660788cbd9483dbb0a0cd20b2b8d43528ad2088bdcccf854039cff00e2827a0d34e9da1de896f2182492efc0976f998aa827d3d334113a74aa9a9298628e74570478bc0c7cf1da83724bb8246d3e6416b0384da61b5501c9f5c3704f152c037561a95f5fce61d3ad6db4ab950f34b331dd9f4191db8fdcd406d67a675ab4b6d325d1af248272a43430315ddec7038f6ad4b3f448bf47eb71cb69abddebf21d5e26896203846c30c8603b9c6452d9835901405660376319ac84bf13180779d8bb82827d4fb0a06f777367a75acd7170f1430a9f331200cfceae061a0cf6dac692d7365266191db0578f5edf3a6075a6c9278b3433188a467860d96fbd40fe540471409aa0c1140750001ed8ed4058e15133c983960077edf6a06faade5c5b7822d2d926766cb967da2341dd8f0727d85033d27597d62e2ee3163756915bbf8799d71e2f19dcbf2a092b88dd9a311950a0e5b70ce47fe6ac18af53f5b69da9752dd69da9ca906876e24465d9e69881c6ff005c679c0aa2bfd267a347512c93dbb5d42d90d3c800b68c9ce0ec3cfa528db74ad034db5905ee8be1ac728dc153984f3f980f4fb56453be2de8f647a6aff53796596f0aed46798ec033ce149c0fb0ad71479c9bb9dc3bf3c55a0b95f65a825150b481a407b93c0fda8a29c06671dc93803bd131eafd0af6dffe18d2ee25982a4b04603b7a9c631fad03bbe586381bc5945b96385718c827db3eb5288eb8ba934eb15fc3c535f05427796dcccdec7150637d5bd55d5362b7975aa4d0d919018adec8637807bb60723000e4f7cd58203538aefa8aeb478a7b9beba924547b8774cf8608036a80704639cf1f9855d1a7f4c68b67a03de5e5d59dad8d988c62e1c0f107a1e7fdf7a082ea6d07a6e3e99375a7cb6b3db093c727701e2360f7f53dfb50653d4130d42ee18f48b3f0232a15218936963ebf5fbd06dbf0cfa74855b9d46e04b730c6144691e12307d33ea7de8348ba6b5478a279a004f98c479247b81f5a9438805ac0be2e02e73c9ef8fbd40c2346d43578eefc40da7da1dc8b8eefea4fcb9fef419beabf12a4bcebcb2d2fa7ee0dc58492084b30236bb6467dce383f6a0b87556a67a7f4d95a0bbb5468816f0a69c78b2e072572719ce78357079dfab3af2e7a92c963b88d94abbbf91cedc93edf418aa2c5f0dbe2a6a9a0c90d8de34773a6a8da1186d6403fa48fec682d9adeb7a9b4c9d572dacc9a6c9700456e5ca910e000ecbd8e580352fb1ae7476bd6dd49a325e5a9f3025245fe961dea097523cc0919a032af039a006936c81423104649c703ef40dcce64bc3035a87b6f0c378f9fe7cf2b8fdf340a4b6e25962915d94a67807839f7a043586922b5636ec44c061063f31f6ab079d7fe19b7eb2d4efeef55d5d74f992e9a0fc3a441dcb13927b838c9aa2d4bf042c618e178efee6e18104870172318edf5c1e6945bbe1a748ea7d2315edbea3a99bcb190030c401010e4e783ee0fa56455be3d6b90c1a6268d69e17f1486900ee98ec29ccc183119419e7e55ba11f089f523ef5058363a8059fb8e31e9421b491056c01819e28d3d0ff07eea3d53a1e3b6b8db235aca63c139c0eea68ca47a9fa6ef757b83ff00bf68ad428c2f248c7a8f9fcea518df516adac74e7544f63a2ea172f1800291e6cee19ec78cd5826344e85b6bad25ba8fade5b99dae0ee11efc71e858f7e7d054a2d7d39a75ae8f7b6b00b8917f1516624b78429da327cec493db1db1d8540cf4aea28f58d6aeae2f6dd64b498082d880488d149fcea7d4939ab04175e6850a8d32de3b78e380c8de32c4db4e18e430fef543cf86fd0d691b4fabdf6648b3b2db69ce7dd87be68342d2f4fb9b5b891af1a28a2dc05bc5036d001e0eef7352884b961a2ea9aa7555c885e08d45b5bc52b61b686c120fb939fb541276bd4b61d53624d942e2f6200bc32290633e99f4233416dd3ad3f0d611c0c77b632e71dc9ef41156dd27a45addcb3dbd9c513b1dd941821bdc7b558333b9f873757fd69a85e3f813e9c7723b5d93265d872473c11544a68ff08fa75e290b42ec4e4124e70738fa5048e89f0f745d2aeadd2decedda6525c975121183c77f7a945c754d0e0d563682ed43425369403bff00bcd58308ba7d5fe13f5a05889974a9d8b46aede4914f707d88ff001528ddf4fd7edb54d1a1d56c312dab2e64dbc9418e78f5c541296d70b716d1cd6f8789977230ecc280cb7519b816f212b205de4e0843ce300f6cfcb39a0545c42cee88e0b458ddec33ee680eac92266360debc7b5056fad2d354b9b189745744be121daf27e550548ce3d4d58324d07a725e98ea2b7ff5381f5169a7579d021fe13904ee43ddfbe49038ab46e76cf05cc714f6d309232a4a98ce54fd6b2196bb7f2e9b631b2c427b891b6851db3eff002007341e5bf887aa2ea3d4f77378be381e42fdb711ed5a1554395caf1cd07617dcd04fc85402101da791421b49920331381c60d1a69bf02f56f03a925b12c162b98c955f775e47df19a32d99b518268e4491668704a79d4aeec7b7bd4a30feb7e9144d76e265697c3e2693631674273803e556087d76f35fd49859e9925ccf611141106f2e182e3241f727f5a94681a268f79ad1b1b8b9dd66b1c2b1ce9bb06361c1e7bf3fe6a096b0d3ba57488e485b52b40909c386901607d47bf7a0ae758eb69ac4d15be81a748f0a9c35cc90b2eff4c03c1c638a0b77405c5d5d45f87be5fe359a88b81b401dc1c7d38fb50586fed18ea3015790091591e447c1518c8c7a0a0a5754d8c9d49a8d9f4ee9dba0b3b5224b9692327728f627e7c6682f9a7e996b6b3a8b6b748a348820c7720761412c064e3041ce282b5d4bd73d3bd3f33daea97ac2e540dd0a292dc8cd043c1f15ba2a7923b65bb910371b9a12141f9d02edf13ba2ade56857551e5e77244c54fd0e280746ebfe99bbbd655d56dcdc9ce08465565f4ee3bfca82d53eb3a6dac3e25c5f5ba646402e33fa77a0aff5b74ad8757e9ca972844aa37c520fcca7d3f5ab067bd369a8f467544d626c98e9f7118f0200e4465c903049c8c9e6ad1b24334b6fa6249716cab20037c309dd83db03b5640dddac3764a4f02cb1103863919fa7a1a06d6f600c37162911b7b252b87dc773f1927393f4a079f868edae1ae6328a8b1ed38e30050226e85d5dc1f879011b3c47c2f604719f9d01eff4f4b83e3c6b18bb452b1cac9b8a83de80b16e8208a3b7b58e1407cc061427cc0ff1560ce7a8f592d69a97504cad2dac01a2b53900c3e9e51ea58f727d0551e73bfb86b99a49a46dcf21c96340dc13804f20f6f9501c0e3b8a0963316fcc4607007f57bd084d64dec01200ce483468ff0040d525d1755b4d4206ff0095207c11dc67ff0019a18f56584f6daad9dade4211e39104a8ded9152b235cd8c530613229c8c1c8ef50472e81690ee00322b0c100f0debdbb7ca8111ace856371358cba85aa5cc407891ccf83f2ef4048b4ad2e59bf116769672c72f99dd1437239078e2824a4d3e1b94559234110e781839fa0a0561b38ad532a12319c86c6307e740a9732a3a00cac870cd8e0faf0681be8b6db965bb909df3c85806eeabced5a09523647e6e0fef419a6adf116daf7ac34be9dd1da686e7f1ca2e243b76320ce57df9ff1560cc3e3f470ff00c78255b842b35bc6c4af9b6e323d3e95467b6365f8dbcf062beb68c119595d8aaff6e282422e9899b4f6bb5d46cda2562a76316c1078f4a0859e1b9b762c0bf94f0e84feb4125a57505c58ea70dd5d0174a986d92b1c13f6f5a0de7a5be366877260b5d42dee2d2423124a487507ebdf15289dd3fac7a7bab6feded74d61733473acdb5a162142ff00313d81ed505fa58fc6d809380c1b9f5c502e0e05040ea367a85dea454de2ff00a610375b04c16c7a16ef8340b5f6930dce9375636acf6a278f04c5dd4f1dbf4a084e91d06f3a52dee62bbd4a2b882494ced3c8a448063b63b638fde803ab7ae749b2b3096d792c93c8c109b55dcd18ce3710473ffdd043dc758dc5869044565aa5dda4c3c2b7bc78c1f14e3963db03e7c0ab066bf1327d41ba76ca6bc48ecad24c456f6b0c87cf8e4bbfa138c0fa9aa3297c83dd4e28395811cf2680a5b93c7ed413cd1ff0f3c797b8031406645236b0508406f30e68ba49c051b97d0e0e7d28ad57e19f575c5be8f269515dac772877c11bc464dea7ba8c739ce78f9d3193bb8ebfea2bcbd6b5b6b8b58bb7f13c2f0ce31cf0deb4c0f2dbad6d743d2ee99efae752d6c02a86e0054524f6383c7ff94c0b6af274c75149a46a5a82c46f1e1479fc3190bd8156fbe7f4a960bf74e9d253f1167a3ac09e0856610e3041ec7f6c540f67b892cee7f8d18368232ef2af2508c7047cf340ead5bf130accc9b1186541e723d09ffc5033bbb1b82d74d6b37f1244daa1b38073df3f4a08eeb1d3b50d4fa6a5b4d32f12cef1902ee73e523d476fde8306eb0d3fabfa4ba92c278af67bb7281606472f90bdd58558253a6afb40ea1d62283a8b461a66a6f931cf6a7c2466f7cfb939e7b5515fbed3747b5eb8f06eb78d35080a2ec9719c76f98049a0b4ebdd37d1bad869acbf0b03c5c16b29444adf50ded41995f68564a263a66b31cd02be152505493f51c1a088bab69ad1bc179e320f07c37c8a0692b46c4995f0381db39a0b2fc34e971d57d4705bc8db6c50ef9dd97b81fcbf7381528f5ae97a1d8e996d1db69b0c7648855b10a81b80f43c739c54134147b9a036063279fb5046e957726a0f2cfe04915b06db1788305ffeac7a0a00d72f8d9c491c06337533050ac7185cf2df6a06da2da4293488f34973328c34aea428c9ec3eded40ee7d2ad249448f6b133820ee2833df3fde819ea96897461b05b87815f2ee919e5d47704fa039ab079b3e326b70eafd4ef6d6650d8e9ebf868b69c8247723efebf2aa280eb9193ebedc5002a124e015340018fb8fde82cf32b1603d0678cd02406dce3008e47ce81b499c331383c9c9f5a2e9c69377369f7d6f796a4acf148acb83fb511e91b3b3d0bab745b7d45acedd8e3732b71b1fd73f7a5a19eafd09a56a0a96b1c705b49c48510761ce4fcfbd4d0d752826b2b583476fc3daacb295b79d768de8a32b1e71f989e49f6a7d14dd1af5ba275a45b8b093c054492ea769092373765c1da4679fbd306e36ba9595fe9f0dcdbcc92c33e1579cf27d0d409ea178f68521b6b76926ee8a7853f7ff140bc768d78f6f73748d1cd103b543f0091cf6efc502f7319dac194371d8b6326829f0c501d7ae6fa568d5d4942c806d4db81839f53c8cd59456fae6e628749b5bab8b1865b08e4726588ec11e7f2e49071c93da9a31dd4341d675e9a5bad374f9858162d0b4ac70e18f0573df35a0c759f87bd53a404f174f965dfff00f479b1ef570576e34bd4b4cc0bdb3b9b7258a00e846e3f2a94376475cee4914af7ca9150685f09ba61efb52fc7dd69bf8eb7c158d1d0b47bb38f37efde968d6eeb4eb5e91d6ad25b660aee59974db6881690918e31ce39279e062a5a34bb57b88adedd1e379679065d80036679e6a07e8391bce7e940c659ef5afe1286de3b16f2b8903094b7b2fa7ce81eb380c4260ed193f2a0cd6fa5d4a4ea0fc7bdadcce923158a3039db83c038e3ef41a0e96b2ad8a35e009291b8a939d9f227e43bd590436bbd6fa269202c974b7123602c76e779624e00e29833bf897d493e896525dbcb2a6b5a9c3e1456b91b6d60cf989c7f31f7a60c02490961ebcf3eb541308e39e067b507007b96007a67fb50178f97eb4165ce18165c2927b773fad023202d9c8dbb7818ff003408300b87f2f1c107d0d0c15a4f2e339c90467f6a18bdfc2cea8ff4bd561b4b9ba686d6e64552c4f954e7d7e46a60f4688d240af1b2bc6cbf5047ca960617ba658de1b792f2d94a5ab33461b18524633fa1a81b5c8b5168967369d23c0e0a24622dc981d81c76aba29df0bb48d660d52fceb88d069f04aeb69130037127f37b9c0ed9a8350781240bbc06da72323b1f7a0eb8816e633192ebc8c9472a78fa50349b4c83c068e24f0ddbcc1c13b837be4d055b57e98b996d4db5b4a893dc1e6620b6ccf2c467efc504ce97a38d3f4d874bf09af6d46e2f25cb82724e791db15650a43f878b51fc34f3da8f132b6d6a98c80a39ff007e99aba249631b58b9047239ec3e55368aeeb7d2da6f52c0eb7f16e87f2c6e836ba90724ab7a67b55d115ac7c3e8aed2182def4c56a14096368959a423d77e3229a27b41e9d8343b01069c8a8dc9660aa3713df3c64d4a1c695d3d6b67a8cba94b9b8d4e61869e4e4a8c636a7f4afcaa09a485519caae19b966f7a0435196582c656b74df3e308beec7b50629375775b691ac5bdb6b16d6378779f019b00a31cf391c9c2f1daae0b35ef52f5374de88d77aa45a6cd25ddc0108694ee2188c28007603d6a0d16c92430a4b2ed3230dc401855cfa0a0a07c45d7b5db9d462e9ee960b14b2ee134ef8c850012147ec78ab0670b643a2efae753d72686e6e2da211db42176079c8e768f65e39f7aa332d6f58bbd635096f6fe6692695b24f603d801e82823cb900ee00e68006460051dfd680ed9f0c905b713d8d006d5f5419fa505a18f94e40501b1b81a04186d62402c87be3d6810b81290aea8467201231cd1749dbc437f9f1e201db3de8ba07dc0175c027f28a335b17c26f888d6b6d0e8fabf892a29c453b1e547f49f7a946d6424f08236491c833ee0835073294888894120700f0280813c40a6711bc8843e00fca7d3ef40e41dc081f9a811681c6f7565329185623b7e9de812b3bcf11ff0b74563bd50494cf120071b97e5fda80d7577046c9019d5669dbc340324eec67fb734103d5da96bf67a7cf0e916f6e2765f25ddc4c11107ab1c8c647cce2816d3ec7f0f6564cae6e67da375e6d52cc4af2e4fb13ed4145f899d47b3499f4bb6d46cda49b69b92921565c3648e3dd40c81cd5c0ae89f13ec246d3e379ed2d6da180b5d34849da1780b128e49271c9f4a60ba685d5fa36bc42d95c324ec7090cc9b1d87b81ed50588958977cacaaa3b9341c655f12348d1dcb8dc1946540f99a019e2134454eeda7bed3839cd052fe2136b536b5d3563a1ca53c49da4b9507198940ce7e5c9fbe281c6b7a974cf4ee4ea7242d76dc784a3c595b3e9b464e3f6ad0ac745ccbd4fadcbabea42da56959a382ce7460d6b1a93c01f97272093ebf6a82f1ad6af0e9da5cb3cecf6902216919f82aa3818c7a9f4c530649a9f5269ba7429d472239bc991a1b0d3c3152880f0f23039e7bf3de90635ab6a377aa5ebdcdecef2c9239e59f3827e5ed54302195fcc38cd01245395c1f5f4a05b606538e483c501b6939e3b5077860f3914165754c33e549000dbe87de813b820c27fa7baafb8a04a69c98e281e42618c795338033df1f3a06c03e4e029247007ad010093c35674da71f977640340081a190658e41c820f141b0fc33f8926c218b4ed609366a02249bb2d19ce3ea4528dbece68eead926b7916689c643a9e0d643387521fea2f693c2d6efc786ee46d9bfed3eff2a04669edf5295ff057a60bd865309246d3bbbedc1efef41d63a8dec9ab4fa7dd4510fc3c69234ca186e2d9c003b7a67bd034bad0a5bb96e25d575267889cc1b54446d9bd0a37bfbfbd02925945a72cba8dddc48b3f87b1e58f23c623f292bdb7fa7cf38a0a5750f54ebba56a9a67fc516b6d6fd3970ea9234677c8dc7f38f6e4640ce282d1ac4b16bfa72c1d2bad430cd1ba822061865f5007d3daac19cf547c189357d561bbd3eee683c62cd786e9b73337b8c7bd512bd39f06adedec2de0d5ae639da372e6485363107f97767b505cee755d03a5e58ac228659af123184b7b733322e38c91dbf5a943ab3d52e64b49ee755d2e64950e238e35f10c884e17cbe87dc540e6d7509a4f110e9f7566a471712850abf6ce463e6280bacea36fd33a4497f773cf32c698dcc4beee33938edc7ad05534aea683ae61d64c4d2a69b6b88d16d5ca5c303f3e386cf61db140e27b5e99e96b64bdd562b6b30aa36c6c37cac7dc9eec6b42c1a66a962fa70beb6b516d0cbe76322f86c78f6c66831bf8b5d5d2dfa35a5dce60b1933b6ce3c788769f2b331ec1b8fd2831b79649984b239773c1dc68129725c1c640e73400ec781d8fb1a03c4a85d0c8582640257bd01e51fc42236263c9c67be280429c6037eb405dbf5fd682c2a0bb976cf07d3fc5009279ef8ec4e68193a9902b28e7dc71fb501d95b098e0f6dd9e0d0049131019b047b8390281bb292484e47c8500c4f242c3076bf704704739a0be7c3febfbae9a5daf23cd017c7e19fb107bb67d0f6fd6837cd2757d1fab34f4f05e37dde630b1c3a91edf4f7159103d6eb7da65fdbdf59dadb5e2460ac876ed9e1c8c060f9efe9c8a0a75cfc42d5742d2ee5a7e9dbb494b6d6b9bc930cce4f940e3cd81ed4160e98f88315e689fff0022b57664199cc5196f0c7a164ef8f98cd0589baffa68590985eb15c0db1985839f6c2919340b69d03f5285bdd6f4bf021424db4329cb153fccc3d09c76a090d3340d2f479a7bab3b38e2924e5e451cfd280d7dafe936f6c5e4bd89813b02a36589ce318a0358dc35cc4e17f9bf234cdbb78fa0c607a7340e6cec20b1596610c6934b8323226379edda81da8dcb9ec40a042f50b5bb21645473b58b11dbd7bfca8304f8add5d67a9ea8ba5d8ea72c1a4d8a952f10f2c920e368cf71e99fad5833dd0754d6ed66bdb2e9a91a5babb2a310465a57c1ddc1038e7bd5171d3748b8d46ee1ff005298dc6a764c27d4eeaee7fe1c01795881c9e7804fe940dbe287c4b6d75a1b1d1c986d62277c91bf131f4c0f6fad0663737135d3b497124924871f98e7803007d2811dc5b83903dc0a0333f03be7de8122df2c9a05a11e5f51f7a05ce7071804fca8033e5da0734020b0183bb23e5416269577ed0e5323078ceeefdff6a03dbcd62914c2f629a47c622689800879e4fbd046f9d8a2a03e31385c0e73da8b83ca590947dcaead8208e73da8849b3e19ce704f7c5015586d006431f5cf61f3a04ee586ff002481c8fe6191408f0011eb8e30682774dea9bbb5784492ca6385832e1ca95e3d2834be9df8c312e2db5eb4375080337000f1303d18763591a469baef4d755989ec6f6dae5a23e20b599406dd8e080ddbed41272f4dd8caf1c86d163910f9595882a3d718a035edd695d3b6a926b57d0ac65b10b4e06eedd863bf141077fd7af2782bd3fa26a1a8891d57c630948c0279393dcd04cf5875258f4de9f0cb7b7b6d66d2b81ba752d85f5214724fed41036bd79d2fe319d7a8f4b9c81e58de2f04827b9ce09a07a3acecf54b790685ace8697606009e52c377b7f2e682b097d7d36acf0f55df5edbdc0977412468cb6ce3be10af3c63b9c8a0b0751f505be9690dd5d752436f62a3fe4c6448f3b7b0c64e38f615734651f107e3045ac42b67a7693018633b965bc1bc838ee173807bf7cd33065baaeb1a95f2c11dfcd2bc51fe48880aa3e8a062a8b059f595df4ae9a74de9e9ec499d43c97b1427c6e47e525bb63e4282ad3ea3712893c599dbc4259c1627713c927de81043950df97db1406da8411c92063be280230839627078e79a0390a71b5bb5003a8c1232338e4507025573e9fbd02a0e41dc0e680c3691cf714053bb34160895dc16f291d98d02322aa39f3e14707ffaa06f202a5bb0c7201f4a343aca51090497efdfbfce89840c8db8e46573923ff14410b00490d9f5c1a0425dd8ce4673e873cd0265e4dbe7041ed814009b8cbb8e5863bd07163b7716e0607b6698060b96b7b9478dc8643918247ee39a60b7e97f133a8b4e0c63d4ee597380923970a3ef4c0e13e25dfcfab457ba95bdbddb212016501867b9cfbfda982f907c74b282da34874a9048aa479c83838edc62982b7ac7c42d235cd67f15ac5b40c366418a2cb0c1c81e6f5e31db14c160d035de8cd4a3f18ea96562cc37359dfe9cac887fef039fd6b39446f56ea5d13a9dca4579a922496b1975b8d22dfc3566cf9557230703be715ac1431d4d2275325d7fae6b4f6f182a93ef1e32a9f41938f6a60afeb1a95c5fea53dccf772cf2c8c489240031f627e7565c0d67bbf160487c1801073bc0c31f91f953420f2bc8c7c52cc540032738a809905c0f4fa501940208e73df34028e703938a0577ae013f4a001300db4f03b71407461ce0502dca8c9c7dcf6a003fafcbdcd0070bc1e0fd734070db467b8a04cb9c9e68274b93bcb1daa40200ed4099765249ec476cf340849b8b264823bf34689ee009cb671df1409bc8e8b8e770e3ec68984d9c953cf97be2860b248caaebc107dc67f7a184c31232db88fd451031ce50e76039f5c8045026efb8f93279e0fd680b239504f0483d88ef409ee25bb90c79c0e050151c6e21b39ce783eb40adbcc2cefa17bdb61322387781c950e3dbdf9c8a066f28790b22e013db3dbef54726081e63c6460d34191b1bb0720f634060e7600412c781502409c8e3d7b500ed71dbef8ed40243f181c0a02e5d4e0fad006f644e4819e3b501f7e3049e7b501bc43b4e391da80558003392d40a23305e320d02e64cf998e1bf5a032b0c927b8e68049c8c8e71c6280377043118f4e680bbff00de0504ddbb3128371c1c64668024e59f3cd02521254e4fad1a2107e48fe6a6809ddb9e78a029e1463d05027ffc744a6c3857c7b1a205ff00e637fbf4a02b12b1794e39f4a02024e7249ed409924720906800005173fd7404989698ee39e4f7a04cf723d07a501fff0097ed406ffe36a018ff00281e99a037f4d0731f3bfd28007e53400ff99a810248c0cf140bc60123233cff008a0557f9beb4056eff007a07109243e79a03778b27bfbd02b128c27039a054001b818a06609de793da815006070283ffd9}\par} +{\pard \ql \f0 \sa0 \li0 \fi0 {\pict\jpegblip\picw250\pich250\picwgoal3000\pichgoal3000 ffd8ffe000104a46494600010101007800780000ffdb00430006040506050406060506070706080a100a0a09090a140e0f0c1017141818171416161a1d251f1a1b231c1616202c20232627292a29191f2d302d283025282928ffdb0043010707070a080a130a0a13281a161a2828282828282828282828282828282828282828282828282828282828282828282828282828282828282828282828282828ffc000110800fa00fa03011100021101031101ffc4001c0000000701010000000000000000000000010203040506070008ffc4003e100002010303020404040502050500030001020300041105122106311322415107617181143291a1234252b1c115f016336272d1082443e1f1265382ffc40017010101010100000000000000000000000000010204ffc4001b11010101010003010000000000000000000001110212213141ffda000c03010002110311003f00dadd18a10a704f6a95ccc57e37750782b0d8d9ea0cd32e7c5446e07e9f4ad723119a7b89e61e348f260719278aad613cbb640002938c76a182b264fc87bd13009c0c019c76e3d68a072e1cf6f4cd502d330c28269a61bb39c923923d4fad44c08dccb95cfd28b8280769ee08a263891e1808739e4f1d8d149392172cc714050dbb9fde8960ed8c60b79b1ed44103b05c331dbdb1dc5026ac1946d20ff8140aa631c773ec738a0346a003bf93e9cf02801895e7b9a01886796c923bd0090a06393c76a0142003ce3d86680d8dd9392303f5341ccc1b3cf7a2c812c37e4923d381429757013209fa511c18146c9247a0f6a007900c0c671c6280854e086c673eb45c27c038fd68aedff2fda836ef881f136f25d5e6b7d1262964aa02b03f98fbf153131935edcc97576f35c33349212cc4f39f7ab26186dfce5b200f73451f7600dcb8cf27e7400c0b291914046c9e0718fde81371b8e7273f4ef4007691919240e714097f31f376e7b5008caee27807b0f5a02c8e1b3c6d27d33cd0201d839523144d1a149ae084b78da47638211771fd050d582c3a0faab5119b6d12f8ab1c06788a0fd4e2ac356fd1fe08754ddccaba849696309e598c9e2103fed1dcfdeadc44fea5ff00a7f956366d375e492403ca935bedcf1eea4ff6ac68a55efc1beb3b552574f8e7009ff933a927ec715bc82b3a8f4d6bba5ca1352d22fe061cf9a0383f71dea5119cc6c0baed3eaac0f1fad40897dcc3d81f7a052366c1007df3400f21edefc5008c28f30c9c5170ee4fc37830086395250a7c66770c18e78da31c0c63de8609b41f7c515c5172a30c3b76344a3e377cb2339cf7a242aea89808cce368272b8c1a2e107c672a49f5c1a181c9c7ae7da8a2119e7b1f5068099ffa68258a132062d8f9e0f34059502b61bf2824e681bb297ced2a71efda80f19c47b9c77fdbe74057c13e539cf3c1a0eeeb9c73f33405ddb4f18249c1e28062b79ae242902024465b9214614649e7bd0362a7249eddc513456e5720f38f5a1a98e96e95d6baa6ebc2d1ad1e65521649bb469f563534d6d7d31f04347d2a2fc5f535db6a0e83718906c887cbbe5a9a8bef44dce9f731ca9a2e89169d6d6f2184b1455dc07b11dcfeb4d16f119c649a681285b03d3e5500f87820ff006a0e098191de80ac9b8904647b55d11da9681a56a31f87a869f6970b8ffe4883629a289aefc16e92d441682da5b098f21ed9f033f353914d19b751fc08d66cc16d12fe2bf45ec92ff0df1fdbfb559ec667aff4eeb1a04db359d3ae6d40eccebe53f46ec7f5ab82263da7dcf3eb5174e5181076918c7de869503232491ee4515c1803824f03b51287f30e0e7d803449494832c157278a2e8c71fcb9f9d144639236824d01e142efb1768cfb9c7ef40512a818de78ff00a682518e7cc30ab9e00a02cce9953247bd41e467191ed9a04205ee99da4e4e3d283a524b0427b5026c18a8e082067db8341ce0e39ed409b6502907391edda80f2dfdc496f0c124ac6184b144cf0a4e338fd2894f7a7342d4ba9b568f4fd261f12571966270a8bfd47d8511bae85f02b47b7fc34bac5d5c5dc88a0c90ab6c8d9bedce3ef4d1ad691a6dae976a96d616d15b409f9638d70054a1dbc68ea51d4329f4619a8022b78e04548515117b05000a035c5c4702a995c26e3819f534047bcb68a458cce866719540724d02e41c0f7a012a40f6141cbc8e7bd01719e38e6838af1c0a04ca8206d3cd037bdb082fad9e0bd8a39e0718649141047d0d5d18f759fc0cd3af164b8e9999acae4e4f81236e898f7c0f55fed574615aee83a96817ef67abda3db4ebdb7f66f983d88a061bb8db9e3d45165076db83c1f950a53780d8247c80a2398f182724f1c7ad080c608cfa7a51a0062adc7afbd0130173bb9c5070f071cb37e82826106e8f615e01c9e680d6b35bc534be3c1e3831b2aa962bb188f2b71df1de819ae4b1048c7f57bd01a58268e332642ae0704f7cf6207af6a01b99e17b7b6416e227407c494139909ed9f4c0a04a4e501e0f1eb40d263e53dce7fa682c9d0bd13abf58dd6db18bc2b157c4975270ab8ef8f563f21447a73a03a1f4de8eb031582b497328066b97fcd21ff038edfde88b7e32703bd64188e7e6283864b73400cd804b67ca3268317eacea6d56ff005233592f8b6303f953fa4af7c2fa93417fe98b763e0ea171297bab98558068f695ce0e08fdbd281e5c6a57ba5e9d14d716ef7774f2ec112601da4f27ec2827ada74bab559a20e148fcae36b0f91140283729c77a0e0a7777a01dac68395719e39a029607cb901b19c501480ab9279f4a086ea8d0b48d76c0586b7143224a76c61ce1831fe93e86b43cd1f12fe19ea7d2533dcdbeebcd20b612651e68f9ece3fcf6fa5067cbcf20ff009a051724905411e94032799060723da8406d6c67e7ea68d0e1770fe5cfb5026c37039ef9a02eca098c91e6e01e71c500b1d8a49c12786cf6a06a4e256008e3d050119958007920e2801154e32fb4120927b014017eb1c523ac5209a356215c291b87be28957ef853f0d66eaa99352d515e1d190f947669ce7b0ffa7e74a8f4be996569a5d9c56b6704705b46bb5238d42851f2ac875712bc70b3c30f892019540704d01ad2669a0491936330c95ce7140b2e4939a03638c7e8680ae485e33bbe540d60d3ada162c90a02c7270a39340a4f28b68da4645007a8f6a069a746f73235ddcefc391e12b2e1916824948742c99382473c73404791c617695279dc0640f9502c578c9efeb4095cb4cb0830ba21cf999c6401f4f5a05061d430c8079a02e03b3004311c7d281b5e3cd676c65489ee594e4aafe6c7ae07a9a0a075bbea3a8ea96f047d3935ebc404f04ad29411e08e011d98fed416fd212ee5b05b4d5ad6300c615807f1171eaa49eff5ad418c7c55f8466dd66d57a521f20cbcd66a7247a9283dbe5418a63862479877cf1f6c5008e400bdf1ce684016fe53dfbd1a73794600e08ce3d6800377c8c7d6800a9cf75fd4503d91492460f7ee3d28247a7b459f5fd592d22711c206f9e563858a31f99cfd050583518ba75247b1d134f9aed21396d4669769931dc01c003f7a329c4d17458ac5b55d36c12e040a3f1da75c1cb04ede2447f7f6a94567ad7a66db4fbbb29ba7d65b8b4bd8ccd09c8231eaa07b8ab04a7c2cf87b3f53ea8d77abc72c1a5dabe2452bb5a561fc83e5ee7e541e988218ed2dd22b7855228d76a46a00000ec00a510bd4dd511f4fe84da95cc31f880022da4902b1e7d3e99ac86fd03d631f565b4ee6d4dbbc649009cab2e48c83f514165b8b94b6895c44f279c280839e78ce28178ae6de46748a789e453865570483ec6812d42e85a421fc37918b00a883924d024c6e99b7a2a966c0009e17dc9f9fed40f81c77e28139218e4ff9815b9cf23340a01c907b9140201038ed402fcafd28386464e4fd33c50272bc60032609cf00fbd024f722dc66f24822ddf972f8feff00e280f69b24844919cac9ce7de83a447f30ded823007b50459d6ecacb528349b979127651b1dc795f1f3f7a0990148054823dc5015d491c0a0c3be337c2ff00c489b5ee9c87172016b9b541c49ff5a8f7f71eb560c1fc43e0a47e1aa94277310431f91fa551c1727f29ed409b641c86e31839a3454805739c1f6a026f1fd740f64665fc8c31cfde82db79bb40e9e8f49b62eb7d7e8b717ec832c91ff247fa1dc7df2281bcc9369d671493c422b7911654c1215f92bb8827bf068624ba635392df5eb4b9924558ee5bc19b71cee43c6dc7cf34c657be8db0b0b9d0f51d2afe668934dbf9628ddb8c2b8c0073f3a80da37546a7d25174fd95dc125c69f7313ee5655dfc313bd483cf07b1f6a68d5b48d5ec758b612e9d7293211c8fe653f35ee2a084eb9e8bb1eafb3582fe496278f3e1c919fcb9f97ad03ee8dd017a6741b6d3229dae161057c5750a48249ec3eb4139238568f6a9e7b103b5037934cb3793c610a2cd9277a8da73f5140ee38f6280c4b11c65b934023006d50050030e4647de80c846de3b500fcf9fbd0197273ed4007b91400e580c8e45074a82400e72682b36fd2162b7f25ddc09af2766ceeb872db79cf00f6a0b3229550140e07007a50092db860673de818df473c862686dad6470d9cce3b7b63e740fa1de6252ebb5bd81cd00bee2d800d003a6464004763ce683ce9f1cbe1f1d3a67ea1d1a30b68edffba814708c7f9c63d0fafceaca31e6dc71e1f07daa82608c83819f7a1a11ce149238fd68d0a579ec682cfd27a7c3a86bd10bc38b3b756b8b93c1fe1a8c91f7381f7a034f752ea5aa5c5eb292f732128037619c018f6ec282e5a2cb047abda74d5ce9b6da80f136de4a496219b3e48c92000323ea73467519d3da5bb757dbda410ac90c77c23058f99007ee7ec31416882ee47d23acb5185caf8bab4691b1efe57fff0038a9457ee75a82f6e7429350466b482f2742c0f74241c80c38c64541a9cfa1e89ac0177d33ab3d8de28f2b5bca429f91140e2c7a9b5ae9fb85b6ea9b46b9b3c796fe040768f76ec0fafb1f9505df4ebdb3d4edd6e74db98ee216fe68ce47d280648f75e2485a44da385ddc13f4a025ddbdbea16a633286566ce55f9c8f6c502ad750db2c514f30dec428247e6340bbf04100b73402afb943ed2b9e30683836defe9403bc1e06734020e06280cafe8683a375941d841c77c1a0151b467b50159f00e4127e5402872371040c5046eb5aadbe9b1c02e2f6dad25b89047099c677b7b0140fe3f1010afc803f3018e68160c3041ee2823f5dba92d34db89a1d9e2843b03b6d05bd013560c1748d57aa2797c6b35bab78e6959dc47231580ff336dcfb03c1a58364b5bbb7d7fa7b7427f1f673830c8664285bd1815238fad20f2c7c41e979ba43aa2e2c1cb1b663bede438f3a13c7dc76fb5515e9065b851f7a02950002a09c51a1b83cf14176e90d3645e9ad7752752aac23b3439c066665c827e944d29a6410aea725c4567135bd840d3c88a723728c29c9efe6c50d3ee9545b0bf8ef2e6e3c2fc2c6f72f2920e5f19039ee4938a9a875d03278377acf52ddf867f036ef71923932bfe51fbd3475cdc369df0db4fb389d4ea37970fa9cc0b00511795ce7d4f181eb4cd2451755fc45ac16d637381b14ca36b641dfce723e4053170d6cb52bbb362f6d3cb19241f2b9029862f09f143549ba7e7d2eef6caf2797c66ee17fdfd69862d1a069da7dfdac579d17adcda5ea9e1a992376c4723e39e3b024fd7e94c458ac3e25dee8d31d3bae74e7b79002bf8b8549471db38f5f4ed4c165e943a06a328d4ba605b4b22a1523c420c64fbaf38a82d36f0ce7cf7463790729b53017e940e0b0ceceed8ce0500e1b70daa08f5c9ed41d271cd0132476e7d7ff00aa069797d2411168ed9a41fcc858211f73c5075acb25ca6fb82aa31e58a36c81f561dcd033d42169e158ac64b98151b3981c2966cf639f4a064c7a8ac55e4865b7d493701e1c8e52403ea3cbfda827e390ca3f2c914aa81991bd281cdacc2747215c60e0ee5c67e940cb51b0b2bcbd824bfb08ee1a252d1caea1821cfa67b1fa504982b2283ce08f518a08abb82f6dd0369a5662081e14ce40c7ae1b04fda82275cb0bfd4f4536f7114589a5412461f3e4ce4e0e060f63f6ab2893d3b4b5b5b78e22ed22aae3cc3cc7e64fad3449a22a461500007602a0cd7e3b74c26b5d2ad79147baf34eccca40e4a7f30ff3f6aba3cd0543267eb5427b86f1f4c76ef45d0eca1ad5ef224d13e1cf4fd9b22192fa67bc955f8c8c617fba9fb510d7a6ed3fd43a735e5b54964be658c048fb6cdd9e7eb8a186bac97d174e6d22e23437b7ac26b95e77c68bf950fa7279e2b22dba45b59e97a669fa4ea36aeff89cea9a90451fc355ff0096ad9f4ce3f41570675d4fa8c77da8de5cde5be26bc653171ca47dc1f6c9fed5562b97f70276808da7c24f0c1c63804e33fa8a2928c0e0383c8f7ed41d92a41393f4a2548595c2c37493db4cd04e8a08f139566edfef3445b6e7aeaf65d2df48ea2b11776ae02a93e564c772adef409f4ee8ba9a21d73a36fa579ad9f325afe599171ed9c30a960d5ba0fe2843abb47a6f510fc26a4c36890f9558fcc6783506a1147b510024e30339ce680d2c6ae9861eb9a009178a0205443b989e39cd01d8075e3047ce80563057ca381ed4011c4531e503d85013c91b804a21279c903341131cda8c3abdc8650f6d20c4321232adec3dc504bab2c113c9293bb1963df3408dd4b75e1efb2856463dbc43b4631fad047e9177ad4fe32ea16b1db4b8fe1aa92571f5f5a0916bc8e0895af5c46c17cd8c9ff7da80f6d736f7f6915c59cab35bc837238ed8a072a31c1ef4062870718a06f7702dc5b3c522ee4752ae0fa8230683c75d6ba3b74ef535fe984929149e4278ca9e47edfdab42058003763ed409f88ffd6dfad06b1f12ae612fa0c76e0b471e9916d23f973eb4158d3efeff004a984da5debc1295d8e4018dbf3145d583a2ad96f356bbd7f5d90dc59587f1e79a6392f28fcaa3ee47159444ea3aa5ddfc7acf50dcdc344d7a4dbc317f52641200f6000fdeb41b5ef51d8eab672ffa9e971c97c11638268e431a46000012a3b9a351567db823b11f3ef40948e428048207a8340ab48ae83cb83ee0f3428a982719edf3e68c9cc97d3fe15ad8c9be138f2bf38e7b8f6ef40f7a5f55bdd3f56b46d3649127f1405f08e7249c76f5fa50689d48ba5f545cdcbdb462cba9206411b2b055bb07d4fb1c73528d4fa8f52d62cf47b6b8d2e65fc458c49f8a818795c151939f977a823ba0fe253750eb7fe937b04293f9f6c90be41dbdc7ff006283473c1efc1a06f69776d73bbf0f2aca32572bc80470450284a46dfca19f819f5a04e799614def26c0bdce09cfd85045dc75769d12dc3c3e2491db0dd3c85195235f7c91cfd066ae0cdba9be31f4ec61a386c1ef9d4ee473e45cfb1cf34c101d3ff1ac9d481d46c628ed24751881880833f988e7b0fa5328dfed2f2def2ce2b9b79925b791772ca87208f7a60182ee2b95cc0c48f53823fbd40ac658b30f4f4a086d4ee1d75bb6b78f4e965596366fc5211b23238008fde81f43692da5bc30d97831a0397dc09e3d714087506bf61a2c4cd77324726d2caaec141f9fd2ae0c435bf8c57173ad7876f7a2daca10489121244cdf319ce3dbf5a834fe81f881a6f57bcb6ba7c53c72c11873e28cee1db391dbef4199ff00ea4348116a5a66a8a8a04aad04847a90723f6ad7d18c312ddc02a3815423ba0f63fa541687bd9efe1b533b3c9e0a78473e899e318a09bd0ba6eef543e3b2bd8e9b10064bd9e4da001dc81401aeeb29a984d0ba7d5e1d06d4e6594f06523bc8e7f5c0ac8af752dfc17d7090d9218ec6d9447129ee71fcc4fb9cd6842ab10dc0014f3e5a2c1704b671dfdc734525226dc939e283a362c7f940344a380393df144733e2276e38f5efcd01b4bbbfc3dda4a9298a44395902e4a9c70682660d4265d62de40b1bdc1545054f95c8fe627df141af7c3af8808f3dd68dd5d2a45765884b8908d8c3b6c27b7a77a945d7a5fa474bd2ba8e4d5748b28624955d5d8b13b79ee9e983d8d40a753758c7a46b96f6114725dc92279a2810b3a64f94900763cfafa503fd3b59b79ed84da34713c0cd890f0a158fa1f981de826e1b548959fc4dc5cee24b6467e59ed4101ff19e9f676baa5d6a72c50adb4ad1ac790ccc076200f7ad41e7df881d79a87576a5f87b0f161d381db1c2a36e7e6d8ff3416bf87ff082c6f208ef7a82f22b9761bd6d619785f6dc477fa53705ab57f83bd297ceb1e9caf67708db9c4526723e849e3e94f212dd25d117fd29a8c09a76b534fa39cf8b6b71ced38e36fb73417f52e64548e34007e673e9f21ef590a1c918c90718dc281a69b68f67118d9da5058b798f6fa7fe280daadd1b2d36eae70710c4d263df0a4d583cc7a668fd4bf11b5837d7c93dcd9a3146959822a0e781f4cfa55161e9dd7fa67a4f55b9e9aea3e9f81fc09ca0ba118998fcdb2338c7b528d39f4cd2ba76e2d357d292df4eb391809963420ce1b1b576fa1e7359119f1eb4e17dd033ca172d6b2a4df303383fdeb5c8f2eef3bce4e0e335684cb0c9f354160d36f64b0baf16072b91b5f03391f43c51aab23a5debe91c4fad4d73689e6fc3a290573ff4f03e59f4a3280d67581ce916567f84b58ce0a1fccec3d58fa9a084de08c90464e4d1a8e419059b201f4a05630a176918efc50176293872c17bf14042aa0125b03db14046c60b60123fde6827fa0c68edd5365ff11346ba6292ee64194240c807e59a32b7fc51bfe8bd5ed5db424860beb62b89218422ce09c11c01dbbd0660ae110bf1bf2154838dbebfefeb41a8f4cdac7f117458f4d9ecd2df53b4cf81a822808c47255c0f7c8e7fb54a2ec2cfabba3b4b4b8d3af12eedad40926b0f070a13f9b633649f7a82eba6ea4357d321d4ecad512daf20df26e016507fa4fbfaf3e98f9d067dd2bd2faac9aa4d72d72d1e9510ca46a7631c7a320e18f1dfd7bd059afb7da816d23de4ba5de211346a1e4785f190548e4648c63b64e6b43ce9d5baafe3b539c5b452dbda46c638a167cb281c73ee4ff9340e3a3fa5f5aea4ba58f4bb57dbfcf2b02a8bf7f7a0de3a5fa0b50d2a2d92eb3e048c0a97c867dbedcf6a944e5cf4f6b76d1b3d8ea42795066266c87c81c65b9cfaf15048e83af3cd64abac08edaf01546c38dae4e0657ee6826e5b892de3702292e2545ddb55700fd0fbfca81c4b3bc718716eef9eeaa402280d14ab3c0b2c65c06fe571823ed40df56b217fa6dd5ab9216689a33f2c8c558307e83b8d77a37aaa7d22f2512c28768800c9954671b3d33ebef568d0ef7a7749eb0b5bbbb162d657b32b46d2e1564c8ed9c5644d1b0b9bbd261d2a440af6cb0e2e5b1e7dbc1238e0f7a0375b696daa7496a3a4dac8a92cf078685b271db04d391e40d5ec4586a1716de2a49e0c8c85d3b120f715ba1899173ff305413070abd89cfe9f5a2d3ee9c8639fa874eb6b804c52dc46b20c9f302c3bd11e84d47e1af4d5dc6521d3e3b662c19a58721ff5a9a321f89bd27a374b456d158dccd34d333332c9b4b2afbe47a7cb1f7aa33d2bc0d8c0f1c8f6a2c14b6d501b39cf63450897380c319e3de8065031c038f7ed40d8faf1ce41e4d004876a8dc3cc7e743025c956c818028c904579e7f0e15695c9c0541924f6c00283d0bf07f42d6b48820b8d62d20b2b58d656404959e52f83c8ff00fcfafbd4a35bb06f12391a48dd55cee2b2f3818ed8f6a8158a159890f02242079147623e631c502b0db436d1ecb7458d4738038fb0a087d6eeb508f48bb7d32d95750752b6c26c905b3ddb6f61eb574794f5cb6b9d0fa9678b512b25d24bbe52b8c1638278fbd582c57ff12afaed45b5bc0d0d8a8c08a2731ee3eec5793f40450466a1d59af446293c186cd53ca0c36eab93dc649e49fbd048e89f1675ed35e301e293919dcbf9867b37cbe94a35fe94ea4d33aba6824306dc48015750d86c6e247b0cf63591a40b8dc23fc30f14138dcac3000f9d03687547f12e8dd5af816b13148dddbcd29039c0f6f6f7a0eb5d62caf5636825db70c9bc4328f0dc0271c8a090627d3073ce681acf6505ccf14d35bc2f2c2731bb28254fb8a075144a83ca806792400334049ee6281e2496408656d880ff0031f61fa50446bd76058ea1b9e21025a3bb48afe71df9c7b71de9c8f196a0de23ca7b827d4f7add117e0cbfd4b5059392369663ff004e71c51aa97e8f555eadd258f2bf8a889cff00dc28cbd0bf123a926e96d163bdb74490bca2321c678209ff001591e71eafd7a7d7ef45cde2c20aae144638033fb9ad2e1b5e69d058da431ccf21d4a5c3b4631b62523807feaf5c7a50222f2d648c25f5aeec8c2cd19dae3d3e87e944d3eb7e90d425b49ef2292de38224f1505c3f8724a9eeaa7bd0d57a60406059436306868a7803839c7ad1a158039c13f4a33a716767f8cb9b6b55e1ae2458813e9938cd07a9f42d0b4de99b4b7d1f41b58ff19b03c93ba06607fa8b1f5f619a5b8266d74a65d42da6ba90cce996dcdc8c9fff006a5a2c2635083b05ef83eb5028076341db4b1ed9f7a04651fc41db18ed419d75b744dbea335fcb0db0335f2057901c05da73c8f9d5d18a75174a3f4c47335e35da4ce418a489374254f707d463d33565d1529b569a489a17944b06ec8057d71dcd037b4b6b8bfba31584124b27e62a8a4f1ea68357f83da7ea5a76bfe0912453ccabb49194653cb60f6ce3dfda983d196cd108c2401711f9768e306b2297d73fc6d02773a8b591922693c5004bb9d72542fa2f6efde8314ff867aeeec27500b77bb5670e36ca19b1dff2e7f2fd2837ce8bd5dd348b78b552219022870d9c46e792a4f6c608a0b846c8e03232b29ec41cd0199f1410fd4b24b1e8f712c0a5e4452d851e6c639dbf3238a0afa42ba77475e4ba8470896681da45180b18da76af3c9029c8f26dc1df2b9c606e273e86b743331924f27f4a82c12280e59b008e79f6a2d4d74188ff00e30d203a82ad7519c1ff00b860d11ba7c5e86c9fa3afae6f4091e043e021270b21e01c7dcd6479ab4dd3aeb56be4b7b184cf2b301b57d07bfd2b4bad0fe25e9f6960ba7c7a55ac50cd750335ccaade7723b83b8f6e38a2207a5ba4e7ea3d93780cb616ca53781f99fbff009a0b675a5be9765d43a75a6ad3b25adb4185429b831c70303dfdfd2831eb8954ca48f3827819c71ed406b2b1b9bf9a5fc1c4ce2253238047957dc9345d122b792eee522811a495ce1157b93ed444ff0049f476b1aaf51c761345269d25be269259570c833c6077249e062a68f53e8ef0da69509d4ae225b92a04af232ab16f98cf1f4a5a266d4dbca8af13a329ecca723f51502d14f0cb9f05d1c8ee01c91f6a0393b4edfe63c8a031608859b38f97340d84d04e5846eae50f9829ce3eb400fb24466041f5e3d2823f56d22db57b192d6e61468a41c823ff0035651916bbf04ada7badda5cad6d1b72c09dc33f2a6875d25f0865d06fe2bc6d4c4d3282026cca8cfafcfd29a34cd234a10c768f711a78f1bb392a3001208e3ec69a26a58d640c832091c90706a084ea1d3eeafdadf4f86da3166c0b4b397c18f046140f5ce4d04f4702436e91c28a9122e028ed8a0a9f5a5b6a09a1bc5a135bc72cce048b3c5bc15c638f9d59043fc2db997481aa69dae49e1cb6bb643239211939e467818f97bd305965ebce9a10bc8da9dbaa2679dd9ce3d8530572cfac87566ab05ae9f1490692b9696e1f833738555f96793504df5f25945d2576b7ec16dc46792381c7b7ad5e60f234980e42f6c9c56a82ec3eff00bd4124e49700f1c646e3cd169ce9575f83d52cee324347323f6e3861ff008a23d47d4ba6a75074fdcd8ef317e2e2ff0098bdd4706a60c3f4ae8cd5f44eb8fc3e97248a638cbc73bf90483d463b373e9574685abf42a6b5649fea72bbdeac4a8d3b018cfae31f7a6895b6b29b41d30d8e9f6bbed9213e1b7a994e724fcbb5064bd7835a9752d3af75d8116354778f660788cbd9483dbb0a0cd20b2b8d43528ad2088bdcccf854039cff00e2827a0d34e9da1de896f2182492efc0976f998aa827d3d334113a74aa9a9298628e74570478bc0c7cf1da83724bb8246d3e6416b0384da61b5501c9f5c3704f152c037561a95f5fce61d3ad6db4ab950f34b331dd9f4191db8fdcd406d67a675ab4b6d325d1af248272a43430315ddec7038f6ad4b3f448bf47eb71cb69abddebf21d5e26896203846c30c8603b9c6452d9835901405660376319ac84bf13180779d8bb82827d4fb0a06f777367a75acd7170f1430a9f331200cfceae061a0cf6dac692d7365266191db0578f5edf3a6075a6c9278b3433188a467860d96fbd40fe540471409aa0c1140750001ed8ed4058e15133c983960077edf6a06faade5c5b7822d2d926766cb967da2341dd8f0727d85033d27597d62e2ee3163756915bbf8799d71e2f19dcbf2a092b88dd9a311950a0e5b70ce47fe6ac18af53f5b69da9752dd69da9ca906876e24465d9e69881c6ff005c679c0aa2bfd267a347512c93dbb5d42d90d3c800b68c9ce0ec3cfa528db74ad034db5905ee8be1ac728dc153984f3f980f4fb56453be2de8f647a6aff53796596f0aed46798ec033ce149c0fb0ad71479c9bb9dc3bf3c55a0b95f65a825150b481a407b93c0fda8a29c06671dc93803bd131eafd0af6dffe18d2ee25982a4b04603b7a9c631fad03bbe586381bc5945b96385718c827db3eb5288eb8ba934eb15fc3c535f05427796dcccdec7150637d5bd55d5362b7975aa4d0d919018adec8637807bb60723000e4f7cd58203538aefa8aeb478a7b9beba924547b8774cf8608036a80704639cf1f9855d1a7f4c68b67a03de5e5d59dad8d988c62e1c0f107a1e7fdf7a082ea6d07a6e3e99375a7cb6b3db093c727701e2360f7f53dfb50653d4130d42ee18f48b3f0232a15218936963ebf5fbd06dbf0cfa74855b9d46e04b730c6144691e12307d33ea7de8348ba6b5478a279a004f98c479247b81f5a9438805ac0be2e02e73c9ef8fbd40c2346d43578eefc40da7da1dc8b8eefea4fcb9fef419beabf12a4bcebcb2d2fa7ee0dc58492084b30236bb6467dce383f6a0b87556a67a7f4d95a0bbb5468816f0a69c78b2e072572719ce78357079dfab3af2e7a92c963b88d94abbbf91cedc93edf418aa2c5f0dbe2a6a9a0c90d8de34773a6a8da1186d6403fa48fec682d9adeb7a9b4c9d572dacc9a6c9700456e5ca910e000ecbd8e580352fb1ae7476bd6dd49a325e5a9f3025245fe961dea097523cc0919a032af039a006936c81423104649c703ef40dcce64bc3035a87b6f0c378f9fe7cf2b8fdf340a4b6e25962915d94a67807839f7a043586922b5636ec44c061063f31f6ab079d7fe19b7eb2d4efeef55d5d74f992e9a0fc3a441dcb13927b838c9aa2d4bf042c618e178efee6e18104870172318edf5c1e6945bbe1a748ea7d2315edbea3a99bcb190030c401010e4e783ee0fa56455be3d6b90c1a6268d69e17f1486900ee98ec29ccc183119419e7e55ba11f089f523ef5058363a8059fb8e31e9421b491056c01819e28d3d0ff07eea3d53a1e3b6b8db235aca63c139c0eea68ca47a9fa6ef757b83ff00bf68ad428c2f248c7a8f9fcea518df516adac74e7544f63a2ea172f1800291e6cee19ec78cd5826344e85b6bad25ba8fade5b99dae0ee11efc71e858f7e7d054a2d7d39a75ae8f7b6b00b8917f1516624b78429da327cec493db1db1d8540cf4aea28f58d6aeae2f6dd64b498082d880488d149fcea7d4939ab04175e6850a8d32de3b78e380c8de32c4db4e18e430fef543cf86fd0d691b4fabdf6648b3b2db69ce7dd87be68342d2f4fb9b5b891af1a28a2dc05bc5036d001e0eef7352884b961a2ea9aa7555c885e08d45b5bc52b61b686c120fb939fb541276bd4b61d53624d942e2f6200bc32290633e99f4233416dd3ad3f0d611c0c77b632e71dc9ef41156dd27a45addcb3dbd9c513b1dd941821bdc7b558333b9f873757fd69a85e3f813e9c7723b5d93265d872473c11544a68ff08fa75e290b42ec4e4124e70738fa5048e89f0f745d2aeadd2decedda6525c975121183c77f7a945c754d0e0d563682ed43425369403bff00bcd58308ba7d5fe13f5a05889974a9d8b46aede4914f707d88ff001528ddf4fd7edb54d1a1d56c312dab2e64dbc9418e78f5c541296d70b716d1cd6f8789977230ecc280cb7519b816f212b205de4e0843ce300f6cfcb39a0545c42cee88e0b458ddec33ee680eac92266360debc7b5056fad2d354b9b189745744be121daf27e550548ce3d4d58324d07a725e98ea2b7ff5381f5169a7579d021fe13904ee43ddfbe49038ab46e76cf05cc714f6d309232a4a98ce54fd6b2196bb7f2e9b631b2c427b891b6851db3eff002007341e5bf887aa2ea3d4f77378be381e42fdb711ed5a1554395caf1cd07617dcd04fc85402101da791421b49920331381c60d1a69bf02f56f03a925b12c162b98c955f775e47df19a32d99b518268e4491668704a79d4aeec7b7bd4a30feb7e9144d76e265697c3e2693631674273803e556087d76f35fd49859e9925ccf611141106f2e182e3241f727f5a94681a268f79ad1b1b8b9dd66b1c2b1ce9bb06361c1e7bf3fe6a096b0d3ba57488e485b52b40909c386901607d47bf7a0ae758eb69ac4d15be81a748f0a9c35cc90b2eff4c03c1c638a0b77405c5d5d45f87be5fe359a88b81b401dc1c7d38fb50586fed18ea3015790091591e447c1518c8c7a0a0a5754d8c9d49a8d9f4ee9dba0b3b5224b9692327728f627e7c6682f9a7e996b6b3a8b6b748a348820c7720761412c064e3041ce282b5d4bd73d3bd3f33daea97ac2e540dd0a292dc8cd043c1f15ba2a7923b65bb910371b9a12141f9d02edf13ba2ade56857551e5e77244c54fd0e280746ebfe99bbbd655d56dcdc9ce08465565f4ee3bfca82d53eb3a6dac3e25c5f5ba646402e33fa77a0aff5b74ad8757e9ca972844aa37c520fcca7d3f5ab067bd369a8f467544d626c98e9f7118f0200e4465c903049c8c9e6ad1b24334b6fa6249716cab20037c309dd83db03b5640dddac3764a4f02cb1103863919fa7a1a06d6f600c37162911b7b252b87dc773f1927393f4a079f868edae1ae6328a8b1ed38e30050226e85d5dc1f879011b3c47c2f604719f9d01eff4f4b83e3c6b18bb452b1cac9b8a83de80b16e8208a3b7b58e1407cc061427cc0ff1560ce7a8f592d69a97504cad2dac01a2b53900c3e9e51ea58f727d0551e73bfb86b99a49a46dcf21c96340dc13804f20f6f9501c0e3b8a0963316fcc4607007f57bd084d64dec01200ce483468ff0040d525d1755b4d4206ff0095207c11dc67ff0019a18f56584f6daad9dade4211e39104a8ded9152b235cd8c530613229c8c1c8ef50472e81690ee00322b0c100f0debdbb7ca8111ace856371358cba85aa5cc407891ccf83f2ef4048b4ad2e59bf116769672c72f99dd1437239078e2824a4d3e1b94559234110e781839fa0a0561b38ad532a12319c86c6307e740a9732a3a00cac870cd8e0faf0681be8b6db965bb909df3c85806eeabced5a09523647e6e0fef419a6adf116daf7ac34be9dd1da686e7f1ca2e243b76320ce57df9ff1560cc3e3f470ff00c78255b842b35bc6c4af9b6e323d3e95467b6365f8dbcf062beb68c119595d8aaff6e282422e9899b4f6bb5d46cda2562a76316c1078f4a0859e1b9b762c0bf94f0e84feb4125a57505c58ea70dd5d0174a986d92b1c13f6f5a0de7a5be366877260b5d42dee2d2423124a487507ebdf15289dd3fac7a7bab6feded74d61733473acdb5a162142ff00313d81ed505fa58fc6d809380c1b9f5c502e0e05040ea367a85dea454de2ff00a610375b04c16c7a16ef8340b5f6930dce9375636acf6a278f04c5dd4f1dbf4a084e91d06f3a52dee62bbd4a2b882494ced3c8a448063b63b638fde803ab7ae749b2b3096d792c93c8c109b55dcd18ce3710473ffdd043dc758dc5869044565aa5dda4c3c2b7bc78c1f14e3963db03e7c0ab066bf1327d41ba76ca6bc48ecad24c456f6b0c87cf8e4bbfa138c0fa9aa3297c83dd4e28395811cf2680a5b93c7ed413cd1ff0f3c797b8031406645236b0508406f30e68ba49c051b97d0e0e7d28ad57e19f575c5be8f269515dac772877c11bc464dea7ba8c739ce78f9d3193bb8ebfea2bcbd6b5b6b8b58bb7f13c2f0ce31cf0deb4c0f2dbad6d743d2ee99efae752d6c02a86e0054524f6383c7ff94c0b6af274c75149a46a5a82c46f1e1479fc3190bd8156fbe7f4a960bf74e9d253f1167a3ac09e0856610e3041ec7f6c540f67b892cee7f8d18368232ef2af2508c7047cf340ead5bf130accc9b1186541e723d09ffc5033bbb1b82d74d6b37f1244daa1b38073df3f4a08eeb1d3b50d4fa6a5b4d32f12cef1902ee73e523d476fde8306eb0d3fabfa4ba92c278af67bb7281606472f90bdd58558253a6afb40ea1d62283a8b461a66a6f931cf6a7c2466f7cfb939e7b5515fbed3747b5eb8f06eb78d35080a2ec9719c76f98049a0b4ebdd37d1bad869acbf0b03c5c16b29444adf50ded41995f68564a263a66b31cd02be152505493f51c1a088bab69ad1bc179e320f07c37c8a0692b46c4995f0381db39a0b2fc34e971d57d4705bc8db6c50ef9dd97b81fcbf7381528f5ae97a1d8e996d1db69b0c7648855b10a81b80f43c739c54134147b9a036063279fb5046e957726a0f2cfe04915b06db1788305ffeac7a0a00d72f8d9c491c06337533050ac7185cf2df6a06da2da4293488f34973328c34aea428c9ec3eded40ee7d2ad249448f6b133820ee2833df3fde819ea96897461b05b87815f2ee919e5d47704fa039ab079b3e326b70eafd4ef6d6650d8e9ebf868b69c8247723efebf2aa280eb9193ebedc5002a124e015340018fb8fde82cf32b1603d0678cd02406dce3008e47ce81b499c331383c9c9f5a2e9c69377369f7d6f796a4acf148acb83fb511e91b3b3d0bab745b7d45acedd8e3732b71b1fd73f7a5a19eafd09a56a0a96b1c705b49c48510761ce4fcfbd4d0d752826b2b583476fc3daacb295b79d768de8a32b1e71f989e49f6a7d14dd1af5ba275a45b8b093c054492ea769092373765c1da4679fbd306e36ba9595fe9f0dcdbcc92c33e1579cf27d0d409ea178f68521b6b76926ee8a7853f7ff140bc768d78f6f73748d1cd103b543f0091cf6efc502f7319dac194371d8b6326829f0c501d7ae6fa568d5d4942c806d4db81839f53c8cd59456fae6e628749b5bab8b1865b08e4726588ec11e7f2e49071c93da9a31dd4341d675e9a5bad374f9858162d0b4ac70e18f0573df35a0c759f87bd53a404f174f965dfff00f479b1ef570576e34bd4b4cc0bdb3b9b7258a00e846e3f2a94376475cee4914af7ca9150685f09ba61efb52fc7dd69bf8eb7c158d1d0b47bb38f37efde968d6eeb4eb5e91d6ad25b660aee59974db6881690918e31ce39279e062a5a34bb57b88adedd1e379679065d80036679e6a07e8391bce7e940c659ef5afe1286de3b16f2b8903094b7b2fa7ce81eb380c4260ed193f2a0cd6fa5d4a4ea0fc7bdadcce923158a3039db83c038e3ef41a0e96b2ad8a35e009291b8a939d9f227e43bd590436bbd6fa269202c974b7123602c76e779624e00e29833bf897d493e896525dbcb2a6b5a9c3e1456b91b6d60cf989c7f31f7a60c02490961ebcf3eb541308e39e067b507007b96007a67fb50178f97eb4165ce18165c2927b773fad023202d9c8dbb7818ff003408300b87f2f1c107d0d0c15a4f2e339c90467f6a18bdfc2cea8ff4bd561b4b9ba686d6e64552c4f954e7d7e46a60f4688d240af1b2bc6cbf5047ca960617ba658de1b792f2d94a5ab33461b18524633fa1a81b5c8b5168967369d23c0e0a24622dc981d81c76aba29df0bb48d660d52fceb88d069f04aeb69130037127f37b9c0ed9a8350781240bbc06da72323b1f7a0eb8816e633192ebc8c9472a78fa50349b4c83c068e24f0ddbcc1c13b837be4d055b57e98b996d4db5b4a893dc1e6620b6ccf2c467efc504ce97a38d3f4d874bf09af6d46e2f25cb82724e791db15650a43f878b51fc34f3da8f132b6d6a98c80a39ff007e99aba249631b58b9047239ec3e55368aeeb7d2da6f52c0eb7f16e87f2c6e836ba90724ab7a67b55d115ac7c3e8aed2182def4c56a14096368959a423d77e3229a27b41e9d8343b01069c8a8dc9660aa3713df3c64d4a1c695d3d6b67a8cba94b9b8d4e61869e4e4a8c636a7f4afcaa09a485519caae19b966f7a0435196582c656b74df3e308beec7b50629375775b691ac5bdb6b16d6378779f019b00a31cf391c9c2f1daae0b35ef52f5374de88d77aa45a6cd25ddc0108694ee2188c28007603d6a0d16c92430a4b2ed3230dc401855cfa0a0a07c45d7b5db9d462e9ee960b14b2ee134ef8c850012147ec78ab0670b643a2efae753d72686e6e2da211db42176079c8e768f65e39f7aa332d6f58bbd635096f6fe6692695b24f603d801e82823cb900ee00e68006460051dfd680ed9f0c905b713d8d006d5f5419fa505a18f94e40501b1b81a04186d62402c87be3d6810b81290aea8467201231cd1749dbc437f9f1e201db3de8ba07dc0175c027f28a335b17c26f888d6b6d0e8fabf892a29c453b1e547f49f7a946d6424f08236491c833ee0835073294888894120700f0280813c40a6711bc8843e00fca7d3ef40e41dc081f9a811681c6f7565329185623b7e9de812b3bcf11ff0b74563bd50494cf120071b97e5fda80d7577046c9019d5669dbc340324eec67fb734103d5da96bf67a7cf0e916f6e2765f25ddc4c11107ab1c8c647cce2816d3ec7f0f6564cae6e67da375e6d52cc4af2e4fb13ed4145f899d47b3499f4bb6d46cda49b69b92921565c3648e3dd40c81cd5c0ae89f13ec246d3e379ed2d6da180b5d34849da1780b128e49271c9f4a60ba685d5fa36bc42d95c324ec7090cc9b1d87b81ed50588958977cacaaa3b9341c655f12348d1dcb8dc1946540f99a019e2134454eeda7bed3839cd052fe2136b536b5d3563a1ca53c49da4b9507198940ce7e5c9fbe281c6b7a974cf4ee4ea7242d76dc784a3c595b3e9b464e3f6ad0ac745ccbd4fadcbabea42da56959a382ce7460d6b1a93c01f97272093ebf6a82f1ad6af0e9da5cb3cecf6902216919f82aa3818c7a9f4c530649a9f5269ba7429d472239bc991a1b0d3c3152880f0f23039e7bf3de90635ab6a377aa5ebdcdecef2c9239e59f3827e5ed54302195fcc38cd01245395c1f5f4a05b606538e483c501b6939e3b5077860f3914165754c33e549000dbe87de813b820c27fa7baafb8a04a69c98e281e42618c795338033df1f3a06c03e4e029247007ad010093c35674da71f977640340081a190658e41c820f141b0fc33f8926c218b4ed609366a02249bb2d19ce3ea4528dbece68eead926b7916689c643a9e0d643387521fea2f693c2d6efc786ee46d9bfed3eff2a04669edf5295ff057a60bd865309246d3bbbedc1efef41d63a8dec9ab4fa7dd4510fc3c69234ca186e2d9c003b7a67bd034bad0a5bb96e25d575267889cc1b54446d9bd0a37bfbfbd02925945a72cba8dddc48b3f87b1e58f23c623f292bdb7fa7cf38a0a5750f54ebba56a9a67fc516b6d6fd3970ea9234677c8dc7f38f6e4640ce282d1ac4b16bfa72c1d2bad430cd1ba822061865f5007d3daac19cf547c189357d561bbd3eee683c62cd786e9b73337b8c7bd512bd39f06adedec2de0d5ae639da372e6485363107f97767b505cee755d03a5e58ac228659af123184b7b733322e38c91dbf5a943ab3d52e64b49ee755d2e64950e238e35f10c884e17cbe87dc540e6d7509a4f110e9f7566a471712850abf6ce463e6280bacea36fd33a4497f773cf32c698dcc4beee33938edc7ad05534aea683ae61d64c4d2a69b6b88d16d5ca5c303f3e386cf61db140e27b5e99e96b64bdd562b6b30aa36c6c37cac7dc9eec6b42c1a66a962fa70beb6b516d0cbe76322f86c78f6c66831bf8b5d5d2dfa35a5dce60b1933b6ce3c788769f2b331ec1b8fd2831b79649984b239773c1dc68129725c1c640e73400ec781d8fb1a03c4a85d0c8582640257bd01e51fc42236263c9c67be280429c6037eb405dbf5fd682c2a0bb976cf07d3fc5009279ef8ec4e68193a9902b28e7dc71fb501d95b098e0f6dd9e0d0049131019b047b8390281bb292484e47c8500c4f242c3076bf704704739a0be7c3febfbae9a5daf23cd017c7e19fb107bb67d0f6fd6837cd2757d1fab34f4f05e37dde630b1c3a91edf4f7159103d6eb7da65fdbdf59dadb5e2460ac876ed9e1c8c060f9efe9c8a0a75cfc42d5742d2ee5a7e9dbb494b6d6b9bc930cce4f940e3cd81ed4160e98f88315e689fff0022b57664199cc5196f0c7a164ef8f98cd0589baffa68590985eb15c0db1985839f6c2919340b69d03f5285bdd6f4bf021424db4329cb153fccc3d09c76a090d3340d2f479a7bab3b38e2924e5e451cfd280d7dafe936f6c5e4bd89813b02a36589ce318a0358dc35cc4e17f9bf234cdbb78fa0c607a7340e6cec20b1596610c6934b8323226379edda81da8dcb9ec40a042f50b5bb21645473b58b11dbd7bfca8304f8add5d67a9ea8ba5d8ea72c1a4d8a952f10f2c920e368cf71e99fad5833dd0754d6ed66bdb2e9a91a5babb2a310465a57c1ddc1038e7bd5171d3748b8d46ee1ff005298dc6a764c27d4eeaee7fe1c01795881c9e7804fe940dbe287c4b6d75a1b1d1c986d62277c91bf131f4c0f6fad0663737135d3b497124924871f98e7803007d2811dc5b83903dc0a0333f03be7de8122df2c9a05a11e5f51f7a05ce7071804fca8033e5da0734020b0183bb23e5416269577ed0e5323078ceeefdff6a03dbcd62914c2f629a47c622689800879e4fbd046f9d8a2a03e31385c0e73da8b83ca590947dcaead8208e73da8849b3e19ce704f7c5015586d006431f5cf61f3a04ee586ff002481c8fe6191408f0011eb8e30682774dea9bbb5784492ca6385832e1ca95e3d2834be9df8c312e2db5eb4375080337000f1303d18763591a469baef4d755989ec6f6dae5a23e20b599406dd8e080ddbed41272f4dd8caf1c86d163910f9595882a3d718a035edd695d3b6a926b57d0ac65b10b4e06eedd863bf141077fd7af2782bd3fa26a1a8891d57c630948c0279393dcd04cf5875258f4de9f0cb7b7b6d66d2b81ba752d85f5214724fed41036bd79d2fe319d7a8f4b9c81e58de2f04827b9ce09a07a3acecf54b790685ace8697606009e52c377b7f2e682b097d7d36acf0f55df5edbdc0977412468cb6ce3be10af3c63b9c8a0b0751f505be9690dd5d752436f62a3fe4c6448f3b7b0c64e38f615734651f107e3045ac42b67a7693018633b965bc1bc838ee173807bf7cd33065baaeb1a95f2c11dfcd2bc51fe48880aa3e8a062a8b059f595df4ae9a74de9e9ec499d43c97b1427c6e47e525bb63e4282ad3ea3712893c599dbc4259c1627713c927de81043950df97db1406da8411c92063be280230839627078e79a0390a71b5bb5003a8c1232338e4507025573e9fbd02a0e41dc0e680c3691cf714053bb34160895dc16f291d98d02322aa39f3e14707ffaa06f202a5bb0c7201f4a343aca51090497efdfbfce89840c8db8e46573923ff14410b00490d9f5c1a0425dd8ce4673e873cd0265e4dbe7041ed814009b8cbb8e5863bd07163b7716e0607b6698060b96b7b9478dc8643918247ee39a60b7e97f133a8b4e0c63d4ee597380923970a3ef4c0e13e25dfcfab457ba95bdbddb212016501867b9cfbfda982f907c74b282da34874a9048aa479c83838edc62982b7ac7c42d235cd67f15ac5b40c366418a2cb0c1c81e6f5e31db14c160d035de8cd4a3f18ea96562cc37359dfe9cac887fef039fd6b39446f56ea5d13a9dca4579a922496b1975b8d22dfc3566cf9557230703be715ac1431d4d2275325d7fae6b4f6f182a93ef1e32a9f41938f6a60afeb1a95c5fea53dccf772cf2c8c489240031f627e7565c0d67bbf160487c1801073bc0c31f91f953420f2bc8c7c52cc540032738a809905c0f4fa501940208e73df34028e703938a0577ae013f4a001300db4f03b71407461ce0502dca8c9c7dcf6a003fafcbdcd0070bc1e0fd734070db467b8a04cb9c9e68274b93bcb1daa40200ed4099765249ec476cf340849b8b264823bf34689ee009cb671df1409bc8e8b8e770e3ec68984d9c953cf97be2860b248caaebc107dc67f7a184c31232db88fd451031ce50e76039f5c8045026efb8f93279e0fd680b239504f0483d88ef409ee25bb90c79c0e050151c6e21b39ce783eb40adbcc2cefa17bdb61322387781c950e3dbdf9c8a066f28790b22e013db3dbef54726081e63c6460d34191b1bb0720f634060e7600412c781502409c8e3d7b500ed71dbef8ed40243f181c0a02e5d4e0fad006f644e4819e3b501f7e3049e7b501bc43b4e391da80558003392d40a23305e320d02e64cf998e1bf5a032b0c927b8e68049c8c8e71c6280377043118f4e680bbff00de0504ddbb3128371c1c64668024e59f3cd02521254e4fad1a2107e48fe6a6809ddb9e78a029e1463d05027ffc744a6c3857c7b1a205ff00e637fbf4a02b12b1794e39f4a02024e7249ed409924720906800005173fd7404989698ee39e4f7a04cf723d07a501fff0097ed406ffe36a018ff00281e99a037f4d0731f3bfd28007e53400ff99a810248c0cf140bc60123233cff008a0557f9beb4056eff007a07109243e79a03778b27bfbd02b128c27039a054001b818a06609de793da815006070283ffd9}\par} +{\pard \ql \f0 \sa0 \li0 \fi0 lalune\par} {\pard \ql \f0 \sa180 \li0 \fi0 Here is a movie {\pict\jpegblip\picw20\pich22\picwgoal400\pichgoal440 ffd8ffe000104a46494600010101004800480000fffe0050546869732061727420697320696e20746865207075626c696320646f6d61696e2e204b6576696e204875676865732c206b6576696e68406569742e636f6d2c2053657074656d6265722031393935ffdb00430001010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101ffdb00430101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101ffc00011080016001403012200021101031101ffc4001a000100020301000000000000000000000000080905060a07ffc400231000010501000300010500000000000000060304050708020001090a11153976b7ffc400160101010100000000000000000000000000060800ffc400261101000102050109000000000000000000010200030405061121b33134365154717475b4ffda000c03010002110311003f00a90cf388f366a62aa720ed6ae07f96901f3831d973452b8cf36fe3570fc908e46d466433e5dd954f2e96992d9e498c7753faa44916e016ca91cc7d88b38fe60a5b97737defcbcc539c98d336a57f4fc2ca9a486bf07ab575ad9a3af4df221d8215e36df86c4504ff0024574551b3d687ee0575757b3ad64e311ee62bd94158d37e24198c43973099f1fc0c41614d950246513a081abf76cfe7061f6863281e6352fd1670949c148dd6dfb0d25f5b3689b1d5c965b0eacbf4e0932ad28e22ab9ae945633f4744bd3c8cee0a7fdf085b9000f449c5f7afa30b83e0b6fd7b0c8429c9467ff9715347c891e25fa24a205861aa715e6a09bd0488237dc2723414d9891381524e8ca7c0894664f835653631ab55ee7e3de433e4ff001b30949124e4c10c8b6ad0a479b3f9c937b2cf5bc0095ad600a0a41a0e9faee174a1c605e161c6c7a313539650b0113190f1a8368e60d5b24f30ff008ea7f0bf867fa6595feeb6978f1fe0f9c26177f4d63a51a9235184750e7d18811339cd000000c75f000e00380380ae390c350def826ed42ad051fa6f501c50f9b699c3b69cbeb76476d202bf3ac985b6e0e968be66572893e6a744540bd9722e5c87956848629bc2559306bd113e8653d3b6aff651dfad7a3ac8b02958cba02a93ccf525757039bae6cff090e1d90688e8aa233ee86a4c4a3e0586d6b2340522e47dcb7d0046d8a5acb05a123ee25d2b230b2ada6e2e2f9ede3c05202520ec2487b0d56562529d8b3393bca76adca4ec1bca508abb001babc007915d84fe3dd14e207e3c62f8379da2a3b861fb6629d28dba53b6ea388ebfed866bf6dfb553455e91ed547ae92e9445253a4fdf3efb4f8ebdfbe7d3c78f1ee0bb9e13e358e942a4ed49e22cff00eeb35fdd7ebfffd9} icon.\par} {\pard \qc \f0 \sa180 \li0 \fi0 \emdash\emdash\emdash\emdash\emdash\par} {\pard \ql \f0 \sa180 \li0 \fi0 \outlinelevel0 \b \fs36 Footnotes\par} diff --git a/test/writer.tei b/test/writer.tei index 1ded37956..7f6bdb4eb 100644 --- a/test/writer.tei +++ b/test/writer.tei @@ -810,8 +810,9 @@ or here: <http://example.com/> <p><figure> <head>lalune</head> <graphic url="lalune.jpg" /> - <figDesc>fig:Voyage dans la Lune</figDesc> + <figDesc>Voyage dans la Lune</figDesc> </figure></p> + <p>lalune</p> <p>Here is a movie <figure> <head>movie</head> <graphic url="movie.jpg" /> diff --git a/test/writer.texinfo b/test/writer.texinfo index ca80f3245..ed12af30f 100644 --- a/test/writer.texinfo +++ b/test/writer.texinfo @@ -1001,7 +1001,6 @@ From ``Voyage dans la Lune'' by Georges Melies (1902): @image{lalune,,,lalune,jpg} @caption{lalune} @end float - Here is a movie @image{movie,,,movie,jpg} icon. @iftex diff --git a/test/writer.textile b/test/writer.textile index b184506b6..201364f37 100644 --- a/test/writer.textile +++ b/test/writer.textile @@ -677,9 +677,18 @@ h1(#images). Images From "Voyage dans la Lune" by Georges Melies (1902): -!lalune.jpg(Voyage dans la Lune)! +<figure> + +<figcaption> + lalune +</figcaption> + +!lalune.jpg(Voyage dans la Lune)! + +</figure> + Here is a movie !movie.jpg(movie)! icon. <hr /> diff --git a/test/writer.xwiki b/test/writer.xwiki index 3695c736e..ed62df3be 100644 --- a/test/writer.xwiki +++ b/test/writer.xwiki @@ -623,8 +623,9 @@ or here: <http://example.com/> From “Voyage dans la Lune” by Georges Melies (1902): -[[image:lalune.jpg||alt="lalune" title="fig:Voyage dans la Lune"]] - +((( +[[image:lalune.jpg||alt="lalune" title="Voyage dans la Lune"]] +))) Here is a movie [[image:movie.jpg||alt="movie"]] icon. diff --git a/test/writer.zimwiki b/test/writer.zimwiki index f793e5760..0196f834d 100644 --- a/test/writer.zimwiki +++ b/test/writer.zimwiki @@ -593,7 +593,9 @@ or here: <http://example.com/> From “Voyage dans la Lune” by Georges Melies (1902): -{{lalune.jpg|Voyage dans la Lune lalune}} +{{lalune.jpg|Voyage dans la Lune}} +lalune + Here is a movie {{movie.jpg|movie}} icon. |
