diff options
author | John MacFarlane <jgm@berkeley.edu> | 2013-01-14 20:53:08 -0800 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2013-01-14 20:53:08 -0800 |
commit | 1a4b47e93368bfbd31daccdfedbd9527ee740201 (patch) | |
tree | 7045c38500930e78c9f0b4aad447a2244fbe64cc /src/Text | |
parent | 56aa257ddb60fb5cd48f8569f66e777454859738 (diff) | |
download | pandoc-1a4b47e93368bfbd31daccdfedbd9527ee740201.tar.gz |
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.
Diffstat (limited to 'src/Text')
-rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 22 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/AsciiDoc.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/ConTeXt.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Docbook.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Docx.hs | 5 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/FB2.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/HTML.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/LaTeX.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Markdown.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/MediaWiki.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Org.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/RST.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Texinfo.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Textile.hs | 3 |
14 files changed, 45 insertions, 18 deletions
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 6ca699d20..1fb361585 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -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 diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs index 30da6ac1a..93d18eff8 100644 --- a/src/Text/Pandoc/Writers/AsciiDoc.hs +++ b/src/Text/Pandoc/Writers/AsciiDoc.hs @@ -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 diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index b9dcf0c71..8f3a9b5cc 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -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 diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index 890feacbf..9f0597722 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -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 diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index 577f9fc84..5f0c01c42 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -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 diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index eeb4616b4..c19390d85 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -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 diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 2d42dd24e..f683e7b62 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -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 diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 035a98170..96549feae 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -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 diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index f658a967d..8cc185010 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -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 diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index a71d7ee7e..38dd969a4 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -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 diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs index 894d4afa0..8aa4a7885 100644 --- a/src/Text/Pandoc/Writers/Org.hs +++ b/src/Text/Pandoc/Writers/Org.hs @@ -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` diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index f3815011f..f347f0188 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -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 diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs index 03e08c463..736c77a21 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -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` diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs index 1f5d3e79d..0f0b477a1 100644 --- a/src/Text/Pandoc/Writers/Textile.hs +++ b/src/Text/Pandoc/Writers/Textile.hs @@ -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 |