Implemented Ext_implicit_figures.
* In markdown reader, add a '\1' character to the beginning of the title of an image that is alone in its paragraph, if implicit_figures extension is selected. * In writers, check for Para [Image alt (src,'\1':tit)] and treat it as a figure if possible. * Updated tests. This is a bit of a hack, but it allows us to make implicit_figures an extension of the markdown reader, rather than the writers.
This commit is contained in:
parent
56aa257ddb
commit
1a4b47e933
17 changed files with 48 additions and 21 deletions
|
@ -770,13 +770,23 @@ compactify'DL items =
|
|||
|
||||
para :: MarkdownParser (F Blocks)
|
||||
para = try $ do
|
||||
exts <- getOption readerExtensions
|
||||
result <- trimInlinesF . mconcat <$> many1 inline
|
||||
option (B.plain <$> result) $ try $ do
|
||||
newline
|
||||
(blanklines >> return mempty)
|
||||
<|> (guardDisabled Ext_blank_before_blockquote >> lookAhead blockQuote)
|
||||
<|> (guardDisabled Ext_blank_before_header >> lookAhead header)
|
||||
return $ B.para <$> result
|
||||
option (B.plain <$> result)
|
||||
$ try $ do
|
||||
newline
|
||||
(blanklines >> return mempty)
|
||||
<|> (guardDisabled Ext_blank_before_blockquote >> lookAhead blockQuote)
|
||||
<|> (guardDisabled Ext_blank_before_header >> lookAhead header)
|
||||
return $ do
|
||||
result' <- result
|
||||
case B.toList result' of
|
||||
[Image alt (src,tit)]
|
||||
| Ext_implicit_figures `Set.member` exts ->
|
||||
-- the \1 at beginning of title indicates a figure
|
||||
return $ B.para $ B.singleton
|
||||
$ Image alt (src,'\1':tit)
|
||||
_ -> return $ B.para result'
|
||||
|
||||
plain :: MarkdownParser (F Blocks)
|
||||
plain = fmap B.plain . trimInlinesF . mconcat <$> many1 inline <* spaces
|
||||
|
|
|
@ -116,6 +116,8 @@ blockToAsciiDoc _ Null = return empty
|
|||
blockToAsciiDoc opts (Plain inlines) = do
|
||||
contents <- inlineListToAsciiDoc opts inlines
|
||||
return $ contents <> cr
|
||||
blockToAsciiDoc opts (Para [Image alt (src,'\1':tit)]) =
|
||||
blockToAsciiDoc opts (Para [Image alt (src,tit)])
|
||||
blockToAsciiDoc opts (Para inlines) = do
|
||||
contents <- inlineListToAsciiDoc opts inlines
|
||||
-- escape if para starts with ordered list marker
|
||||
|
|
|
@ -131,7 +131,8 @@ blockToConTeXt :: Block
|
|||
-> State WriterState Doc
|
||||
blockToConTeXt Null = return empty
|
||||
blockToConTeXt (Plain lst) = inlineListToConTeXt lst
|
||||
blockToConTeXt (Para [Image txt (src,_)]) = do
|
||||
-- title beginning with \1 indicates that the image is a figure
|
||||
blockToConTeXt (Para [Image txt (src,'\1':_)]) = do
|
||||
capt <- inlineListToConTeXt txt
|
||||
return $ blankline $$ "\\placefigure[here,nonumber]" <> braces capt <>
|
||||
braces ("\\externalfigure" <> brackets (text src)) <> blankline
|
||||
|
|
|
@ -144,7 +144,8 @@ blockToDocbook :: WriterOptions -> Block -> Doc
|
|||
blockToDocbook _ Null = empty
|
||||
blockToDocbook _ (Header _ _ _) = empty -- should not occur after hierarchicalize
|
||||
blockToDocbook opts (Plain lst) = inlinesToDocbook opts lst
|
||||
blockToDocbook opts (Para [Image txt (src,_)]) =
|
||||
-- title beginning with \1 indicates that the image is a figure
|
||||
blockToDocbook opts (Para [Image txt (src,'\1':_)]) =
|
||||
let alt = inlinesToDocbook opts txt
|
||||
capt = if null txt
|
||||
then empty
|
||||
|
|
|
@ -347,9 +347,10 @@ blockToOpenXML opts (Header lev (ident,_,_) lst) = do
|
|||
let bookmarkEnd = mknode "w:bookmarkEnd" [("w:id", id')] ()
|
||||
return $ [bookmarkStart] ++ contents ++ [bookmarkEnd]
|
||||
blockToOpenXML opts (Plain lst) = blockToOpenXML opts (Para lst)
|
||||
blockToOpenXML opts (Para x@[Image alt _]) = do
|
||||
-- title beginning with \1 indicates that the image is a figure
|
||||
blockToOpenXML opts (Para [Image alt (src,'\1':tit)]) = do
|
||||
paraProps <- getParaProps
|
||||
contents <- inlinesToOpenXML opts x
|
||||
contents <- inlinesToOpenXML opts [Image alt (src,tit)]
|
||||
captionNode <- withParaProp (pStyle "ImageCaption")
|
||||
$ blockToOpenXML opts (Para alt)
|
||||
return $ mknode "w:p" [] (paraProps ++ contents) : captionNode
|
||||
|
|
|
@ -316,7 +316,9 @@ linkID i = "l" ++ (show i)
|
|||
blockToXml :: Block -> FBM [Content]
|
||||
blockToXml (Plain ss) = cMapM toXml ss -- FIXME: can lead to malformed FB2
|
||||
blockToXml (Para [Math DisplayMath formula]) = insertMath NormalImage formula
|
||||
blockToXml (Para [img@(Image _ _)]) = insertImage NormalImage img
|
||||
-- title beginning with \1 indicates that the image is a figure
|
||||
blockToXml (Para [Image alt (src,'\1':tit)]) =
|
||||
insertImage NormalImage (Image alt (src,tit))
|
||||
blockToXml (Para ss) = liftM (list . el "p") $ cMapM toXml ss
|
||||
blockToXml (CodeBlock _ s) = return . spaceBeforeAfter .
|
||||
map (el "p" . el "code") . lines $ s
|
||||
|
|
|
@ -392,7 +392,8 @@ treatAsImage fp =
|
|||
blockToHtml :: WriterOptions -> Block -> State WriterState Html
|
||||
blockToHtml _ Null = return mempty
|
||||
blockToHtml opts (Plain lst) = inlineListToHtml opts lst
|
||||
blockToHtml opts (Para [Image txt (s,tit)]) = do
|
||||
-- title beginning with \1 indicates that the image is a figure
|
||||
blockToHtml opts (Para [Image txt (s,'\1':tit)]) = do
|
||||
img <- inlineToHtml opts (Image txt (s,tit))
|
||||
let tocapt = if writerHtml5 opts
|
||||
then H5.figcaption
|
||||
|
|
|
@ -277,7 +277,8 @@ blockToLaTeX :: Block -- ^ Block to convert
|
|||
-> State WriterState Doc
|
||||
blockToLaTeX Null = return empty
|
||||
blockToLaTeX (Plain lst) = inlineListToLaTeX lst
|
||||
blockToLaTeX (Para [Image txt (src,tit)]) = do
|
||||
-- title beginning with \1 indicates that the image is a figure
|
||||
blockToLaTeX (Para [Image txt (src,'\1':tit)]) = do
|
||||
capt <- if null txt
|
||||
then return empty
|
||||
else (\c -> "\\caption" <> braces c) `fmap` inlineListToLaTeX txt
|
||||
|
|
|
@ -246,6 +246,9 @@ blockToMarkdown _ Null = return empty
|
|||
blockToMarkdown opts (Plain inlines) = do
|
||||
contents <- inlineListToMarkdown opts inlines
|
||||
return $ contents <> cr
|
||||
-- title beginning with \1 indicates figure
|
||||
blockToMarkdown opts (Para [Image alt (src,'\1':tit)]) =
|
||||
blockToMarkdown opts (Para [Image alt (src,tit)])
|
||||
blockToMarkdown opts (Para inlines) = do
|
||||
contents <- inlineListToMarkdown opts inlines
|
||||
-- escape if para starts with ordered list marker
|
||||
|
|
|
@ -81,7 +81,8 @@ blockToMediaWiki _ Null = return ""
|
|||
blockToMediaWiki opts (Plain inlines) =
|
||||
inlineListToMediaWiki opts inlines
|
||||
|
||||
blockToMediaWiki opts (Para [Image txt (src,tit)]) = do
|
||||
-- title beginning with \1 indicates that the image is a figure
|
||||
blockToMediaWiki opts (Para [Image txt (src,'\1':tit)]) = do
|
||||
capt <- if null txt
|
||||
then return ""
|
||||
else ("|caption " ++) `fmap` inlineListToMediaWiki opts txt
|
||||
|
|
|
@ -114,7 +114,8 @@ blockToOrg :: Block -- ^ Block element
|
|||
-> State WriterState Doc
|
||||
blockToOrg Null = return empty
|
||||
blockToOrg (Plain inlines) = inlineListToOrg inlines
|
||||
blockToOrg (Para [Image txt (src,tit)]) = do
|
||||
-- title beginning with \1 indicates that the image is a figure
|
||||
blockToOrg (Para [Image txt (src,'\1':tit)]) = do
|
||||
capt <- if null txt
|
||||
then return empty
|
||||
else (\c -> "#+CAPTION: " <> c <> blankline) `fmap`
|
||||
|
|
|
@ -148,7 +148,8 @@ blockToRST :: Block -- ^ Block element
|
|||
-> State WriterState Doc
|
||||
blockToRST Null = return empty
|
||||
blockToRST (Plain inlines) = inlineListToRST inlines
|
||||
blockToRST (Para [Image txt (src,tit)]) = do
|
||||
-- title beginning with \1 indicates that the image is a figure
|
||||
blockToRST (Para [Image txt (src,'\1':tit)]) = do
|
||||
capt <- inlineListToRST txt
|
||||
let fig = "figure:: " <> text src
|
||||
let alt = ":alt: " <> if null tit then capt else text tit
|
||||
|
|
|
@ -126,7 +126,8 @@ blockToTexinfo Null = return empty
|
|||
blockToTexinfo (Plain lst) =
|
||||
inlineListToTexinfo lst
|
||||
|
||||
blockToTexinfo (Para [Image txt (src,tit)]) = do
|
||||
-- title beginning with \1 indicates that the image is a figure
|
||||
blockToTexinfo (Para [Image txt (src,'\1':tit)]) = do
|
||||
capt <- if null txt
|
||||
then return empty
|
||||
else (\c -> text "@caption" <> braces c) `fmap`
|
||||
|
|
|
@ -101,7 +101,8 @@ blockToTextile _ Null = return ""
|
|||
blockToTextile opts (Plain inlines) =
|
||||
inlineListToTextile opts inlines
|
||||
|
||||
blockToTextile opts (Para [Image txt (src,tit)]) = do
|
||||
-- title beginning with \1 indicates that the image is a figure
|
||||
blockToTextile opts (Para [Image txt (src,'\1':tit)]) = do
|
||||
capt <- blockToTextile opts (Para txt)
|
||||
im <- inlineToTextile opts (Image txt (src,tit))
|
||||
return $ im ++ "\n" ++ capt
|
||||
|
|
File diff suppressed because one or more lines are too long
|
@ -384,7 +384,7 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,HorizontalRule
|
||||
,Header 1 ("images",[],[]) [Str "Images"]
|
||||
,Para [Str "From",Space,Quoted DoubleQuote [Str "Voyage",Space,Str "dans",Space,Str "la",Space,Str "Lune"],Space,Str "by",Space,Str "Georges",Space,Str "Melies",Space,Str "(1902):"]
|
||||
,Para [Image [Str "lalune"] ("lalune.jpg","Voyage dans la Lune")]
|
||||
,Para [Image [Str "lalune"] ("lalune.jpg","\SOHVoyage dans la Lune")]
|
||||
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image [Str "movie"] ("movie.jpg",""),Space,Str "icon."]
|
||||
,HorizontalRule
|
||||
,Header 1 ("footnotes",[],[]) [Str "Footnotes"]
|
||||
|
|
|
@ -384,7 +384,7 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
|
|||
,HorizontalRule
|
||||
,Header 1 ("images",[],[]) [Str "Images"]
|
||||
,Para [Str "From",Space,Quoted DoubleQuote [Str "Voyage",Space,Str "dans",Space,Str "la",Space,Str "Lune"],Space,Str "by",Space,Str "Georges",Space,Str "Melies",Space,Str "(1902):"]
|
||||
,Para [Image [Str "lalune"] ("lalune.jpg","Voyage dans la Lune")]
|
||||
,Para [Image [Str "lalune"] ("lalune.jpg","\SOHVoyage dans la Lune")]
|
||||
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image [Str "movie"] ("movie.jpg",""),Space,Str "icon."]
|
||||
,HorizontalRule
|
||||
,Header 1 ("footnotes",[],[]) [Str "Footnotes"]
|
||||
|
|
Loading…
Reference in a new issue