Asciidoctor images (#6671)

Support `Asciidoctor`'s block figures.

Closes #6538.
This commit is contained in:
argent0 2020-09-19 22:22:52 -03:00 committed by GitHub
parent caa225ad82
commit ba9bedef23
No known key found for this signature in database
GPG key ID: 4AEE18F83AFDEB23
3 changed files with 43 additions and 28 deletions

View file

@ -66,7 +66,8 @@ writeAsciiDoc opts document =
-- | Convert Pandoc to AsciiDoctor compatible AsciiDoc.
writeAsciiDoctor :: PandocMonad m => WriterOptions -> Pandoc -> m Text
writeAsciiDoctor opts document =
evalStateT (pandocToAsciiDoc opts document) defaultWriterState{ asciidoctorVariant = True }
evalStateT (pandocToAsciiDoc opts document)
defaultWriterState{ asciidoctorVariant = True }
type ADW = StateT WriterState
@ -138,9 +139,11 @@ blockToAsciiDoc opts (Div (id',"section":_,_)
blockToAsciiDoc opts (Plain inlines) = do
contents <- inlineListToAsciiDoc opts inlines
return $ contents <> blankline
blockToAsciiDoc opts (Para [Image attr alt (src,tgt)])
blockToAsciiDoc opts (Para [Image attr alternate (src,tgt)])
-- image::images/logo.png[Company logo, title="blah"]
| Just tit <- T.stripPrefix "fig:" tgt
= blockToAsciiDoc opts (Para [Image attr alt (src,tit)])
= (\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
@ -192,7 +195,8 @@ blockToAsciiDoc opts (BlockQuote blocks) = do
let bar = text "____"
return $ bar $$ chomp contents' $$ bar <> blankline
blockToAsciiDoc opts (Table _ blkCapt specs thead tbody tfoot) = do
let (caption, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
let (caption, aligns, widths, headers, rows) =
toLegacyTable blkCapt specs thead tbody tfoot
caption' <- inlineListToAsciiDoc opts caption
let caption'' = if null caption
then empty
@ -381,7 +385,10 @@ blockListToAsciiDoc opts blocks =
data SpacyLocation = End | Start
-- | Convert list of Pandoc inline elements to asciidoc.
inlineListToAsciiDoc :: PandocMonad m => WriterOptions -> [Inline] -> ADW m (Doc Text)
inlineListToAsciiDoc :: PandocMonad m =>
WriterOptions ->
[Inline] ->
ADW m (Doc Text)
inlineListToAsciiDoc opts lst = do
oldIntraword <- gets intraword
setIntraword False
@ -518,27 +525,8 @@ inlineToAsciiDoc opts (Link _ txt (src, _tit)) = do
return $ if useAuto
then literal srcSuffix
else prefix <> literal src <> "[" <> linktext <> "]"
inlineToAsciiDoc opts (Image attr alternate (src, tit)) = do
-- image:images/logo.png[Company logo, title="blah"]
let txt = if null alternate || (alternate == [Str ""])
then [Str "image"]
else alternate
linktext <- inlineListToAsciiDoc opts txt
let linktitle = if T.null tit
then empty
else ",title=\"" <> literal tit <> "\""
showDim dir = case dimension dir attr of
Just (Percent a) ->
["scaledwidth=" <> text (show (Percent a))]
Just dim ->
[text (show dir) <> "=" <> literal (showInPixel opts dim)]
Nothing ->
[]
dimList = showDim Width ++ showDim Height
dims = if null dimList
then empty
else "," <> mconcat (intersperse "," dimList)
return $ "image:" <> literal src <> "[" <> linktext <> linktitle <> dims <> "]"
inlineToAsciiDoc opts (Image attr alternate (src, tit)) =
("image:" <>) <$> imageArguments opts attr alternate src tit
inlineToAsciiDoc opts (Note [Para inlines]) =
inlineToAsciiDoc opts (Note [Plain inlines])
inlineToAsciiDoc opts (Note [Plain inlines]) = do
@ -556,3 +544,30 @@ inlineToAsciiDoc opts (Span (ident,classes,_) ils) = do
let modifier = brackets $ literal $ T.unwords $
[ "#" <> ident | not (T.null ident)] ++ map ("." <>) classes
return $ modifier <> marker <> contents <> marker
-- | Provides the arguments for both `image:` and `image::`
-- e.g.: sunset.jpg[Sunset,300,200]
imageArguments :: PandocMonad m => WriterOptions ->
Attr -> [Inline] -> Text -> Text ->
ADW m (Doc Text)
imageArguments opts attr altText src title = do
let txt = if null altText || (altText == [Str ""])
then [Str "image"]
else altText
linktext <- inlineListToAsciiDoc opts txt
let linktitle = if T.null title
then empty
else ",title=\"" <> literal title <> "\""
showDim dir = case dimension dir attr of
Just (Percent a) ->
["scaledwidth=" <> text (show (Percent a))]
Just dim ->
[text (show dir) <> "=" <>
literal (showInPixel opts dim)]
Nothing ->
[]
dimList = showDim Width ++ showDim Height
dims = if null dimList
then empty
else "," <> mconcat (intersperse "," dimList)
return $ literal src <> "[" <> linktext <> linktitle <> dims <> "]"

View file

@ -622,7 +622,7 @@ or here: <http://example.com/>
From ``Voyage dans la Lune'' by Georges Melies (1902):
image:lalune.jpg[lalune,title="Voyage dans la Lune"]
image::lalune.jpg[lalune,title="Voyage dans la Lune"]
Here is a movie image:movie.jpg[movie] icon.

View file

@ -623,7 +623,7 @@ or here: <http://example.com/>
From "`Voyage dans la Lune`" by Georges Melies (1902):
image:lalune.jpg[lalune,title="Voyage dans la Lune"]
image::lalune.jpg[lalune,title="Voyage dans la Lune"]
Here is a movie image:movie.jpg[movie] icon.