Use 'fig:' instead of '\SOH' in title to indicate figure.

Revises 1a4b47e933
This commit is contained in:
John MacFarlane 2013-01-15 08:45:46 -08:00
parent 1a4b47e933
commit 7bc37e4414
16 changed files with 29 additions and 29 deletions

View file

@ -783,9 +783,9 @@ para = try $ do
case B.toList result' of
[Image alt (src,tit)]
| Ext_implicit_figures `Set.member` exts ->
-- the \1 at beginning of title indicates a figure
-- the fig: at beginning of title indicates a figure
return $ B.para $ B.singleton
$ Image alt (src,'\1':tit)
$ Image alt (src,'f':'i':'g':':':tit)
_ -> return $ B.para result'
plain :: MarkdownParser (F Blocks)

View file

@ -116,7 +116,7 @@ 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,'f':'i':'g':':':tit)]) =
blockToAsciiDoc opts (Para [Image alt (src,tit)])
blockToAsciiDoc opts (Para inlines) = do
contents <- inlineListToAsciiDoc opts inlines

View file

@ -131,8 +131,8 @@ blockToConTeXt :: Block
-> State WriterState Doc
blockToConTeXt Null = return empty
blockToConTeXt (Plain lst) = inlineListToConTeXt lst
-- title beginning with \1 indicates that the image is a figure
blockToConTeXt (Para [Image txt (src,'\1':_)]) = do
-- title beginning with fig: indicates that the image is a figure
blockToConTeXt (Para [Image txt (src,'f':'i':'g':':':_)]) = do
capt <- inlineListToConTeXt txt
return $ blankline $$ "\\placefigure[here,nonumber]" <> braces capt <>
braces ("\\externalfigure" <> brackets (text src)) <> blankline

View file

@ -144,8 +144,8 @@ blockToDocbook :: WriterOptions -> Block -> Doc
blockToDocbook _ Null = empty
blockToDocbook _ (Header _ _ _) = empty -- should not occur after hierarchicalize
blockToDocbook opts (Plain lst) = inlinesToDocbook opts lst
-- title beginning with \1 indicates that the image is a figure
blockToDocbook opts (Para [Image txt (src,'\1':_)]) =
-- title beginning with fig: indicates that the image is a figure
blockToDocbook opts (Para [Image txt (src,'f':'i':'g':':':_)]) =
let alt = inlinesToDocbook opts txt
capt = if null txt
then empty

View file

@ -347,8 +347,8 @@ 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)
-- title beginning with \1 indicates that the image is a figure
blockToOpenXML opts (Para [Image alt (src,'\1':tit)]) = do
-- title beginning with fig: indicates that the image is a figure
blockToOpenXML opts (Para [Image alt (src,'f':'i':'g':':':tit)]) = do
paraProps <- getParaProps
contents <- inlinesToOpenXML opts [Image alt (src,tit)]
captionNode <- withParaProp (pStyle "ImageCaption")

View file

@ -316,8 +316,8 @@ 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
-- title beginning with \1 indicates that the image is a figure
blockToXml (Para [Image alt (src,'\1':tit)]) =
-- title beginning with fig: indicates that the image is a figure
blockToXml (Para [Image alt (src,'f':'i':'g':':':tit)]) =
insertImage NormalImage (Image alt (src,tit))
blockToXml (Para ss) = liftM (list . el "p") $ cMapM toXml ss
blockToXml (CodeBlock _ s) = return . spaceBeforeAfter .

View file

@ -392,8 +392,8 @@ treatAsImage fp =
blockToHtml :: WriterOptions -> Block -> State WriterState Html
blockToHtml _ Null = return mempty
blockToHtml opts (Plain lst) = inlineListToHtml opts lst
-- title beginning with \1 indicates that the image is a figure
blockToHtml opts (Para [Image txt (s,'\1':tit)]) = do
-- title beginning with fig: indicates that the image is a figure
blockToHtml opts (Para [Image txt (s,'f':'i':'g':':':tit)]) = do
img <- inlineToHtml opts (Image txt (s,tit))
let tocapt = if writerHtml5 opts
then H5.figcaption

View file

@ -277,8 +277,8 @@ blockToLaTeX :: Block -- ^ Block to convert
-> State WriterState Doc
blockToLaTeX Null = return empty
blockToLaTeX (Plain lst) = inlineListToLaTeX lst
-- title beginning with \1 indicates that the image is a figure
blockToLaTeX (Para [Image txt (src,'\1':tit)]) = do
-- title beginning with fig: indicates that the image is a figure
blockToLaTeX (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
capt <- if null txt
then return empty
else (\c -> "\\caption" <> braces c) `fmap` inlineListToLaTeX txt

View file

@ -246,8 +246,8 @@ 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)]) =
-- title beginning with fig: indicates figure
blockToMarkdown opts (Para [Image alt (src,'f':'i':'g':':':tit)]) =
blockToMarkdown opts (Para [Image alt (src,tit)])
blockToMarkdown opts (Para inlines) = do
contents <- inlineListToMarkdown opts inlines

View file

@ -81,8 +81,8 @@ blockToMediaWiki _ Null = return ""
blockToMediaWiki opts (Plain inlines) =
inlineListToMediaWiki opts inlines
-- title beginning with \1 indicates that the image is a figure
blockToMediaWiki opts (Para [Image txt (src,'\1':tit)]) = do
-- title beginning with fig: indicates that the image is a figure
blockToMediaWiki opts (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
capt <- if null txt
then return ""
else ("|caption " ++) `fmap` inlineListToMediaWiki opts txt

View file

@ -114,8 +114,8 @@ blockToOrg :: Block -- ^ Block element
-> State WriterState Doc
blockToOrg Null = return empty
blockToOrg (Plain inlines) = inlineListToOrg inlines
-- title beginning with \1 indicates that the image is a figure
blockToOrg (Para [Image txt (src,'\1':tit)]) = do
-- title beginning with fig: indicates that the image is a figure
blockToOrg (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
capt <- if null txt
then return empty
else (\c -> "#+CAPTION: " <> c <> blankline) `fmap`

View file

@ -148,8 +148,8 @@ blockToRST :: Block -- ^ Block element
-> State WriterState Doc
blockToRST Null = return empty
blockToRST (Plain inlines) = inlineListToRST inlines
-- title beginning with \1 indicates that the image is a figure
blockToRST (Para [Image txt (src,'\1':tit)]) = do
-- title beginning with fig: indicates that the image is a figure
blockToRST (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
capt <- inlineListToRST txt
let fig = "figure:: " <> text src
let alt = ":alt: " <> if null tit then capt else text tit

View file

@ -126,8 +126,8 @@ blockToTexinfo Null = return empty
blockToTexinfo (Plain lst) =
inlineListToTexinfo lst
-- title beginning with \1 indicates that the image is a figure
blockToTexinfo (Para [Image txt (src,'\1':tit)]) = do
-- title beginning with fig: indicates that the image is a figure
blockToTexinfo (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
capt <- if null txt
then return empty
else (\c -> text "@caption" <> braces c) `fmap`

View file

@ -101,8 +101,8 @@ blockToTextile _ Null = return ""
blockToTextile opts (Plain inlines) =
inlineListToTextile opts inlines
-- title beginning with \1 indicates that the image is a figure
blockToTextile opts (Para [Image txt (src,'\1':tit)]) = do
-- title beginning with fig: indicates that the image is a figure
blockToTextile opts (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
capt <- blockToTextile opts (Para txt)
im <- inlineToTextile opts (Image txt (src,tit))
return $ im ++ "\n" ++ capt

View file

@ -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","\SOHVoyage dans la Lune")]
,Para [Image [Str "lalune"] ("lalune.jpg","fig:Voyage 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"]

View file

@ -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","\SOHVoyage dans la Lune")]
,Para [Image [Str "lalune"] ("lalune.jpg","fig:Voyage 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"]