aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--README5
-rw-r--r--pandoc.hs208
-rw-r--r--src/Text/Pandoc/Options.hs26
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs7
4 files changed, 134 insertions, 112 deletions
diff --git a/README b/README
index 20581b26a..cdb5a1226 100644
--- a/README
+++ b/README
@@ -243,6 +243,11 @@ Reader options
`perl,numberLines` or `haskell`. Multiple classes may be separated
by spaces or commas.
+`--default-image-extension=`*EXTENSION*
+: Specify a default extension to use when markdown image paths/URLs have no
+ extension. This allows you to use the same markdown source for
+ formats that require different kinds of images.
+
`--normalize`
: Normalize the document after reading: merge adjacent
`Str` or `Emph` elements, for example, and remove repeated `Space`s.
diff --git a/pandoc.hs b/pandoc.hs
index 2b6ed3a46..dc7de52a8 100644
--- a/pandoc.hs
+++ b/pandoc.hs
@@ -137,61 +137,63 @@ data Opt = Opt
, optSetextHeaders :: Bool -- ^ Use atx headers for markdown level 1-2
, optAscii :: Bool -- ^ Use ascii characters only in html
, optTeXLigatures :: Bool -- ^ Use TeX ligatures for quotes/dashes
+ , optDefaultImageExtension :: String -- ^ Default image extension
}
-- | Defaults for command-line options.
defaultOpts :: Opt
defaultOpts = Opt
- { optTabStop = 4
- , optPreserveTabs = False
- , optStandalone = False
- , optReader = "" -- null for default reader
- , optWriter = "" -- null for default writer
- , optParseRaw = False
- , optTableOfContents = False
- , optTransforms = []
- , optTemplate = Nothing
- , optVariables = []
- , optOutputFile = "-" -- "-" means stdout
- , optNumberSections = False
- , optSectionDivs = False
- , optIncremental = False
- , optSelfContained = False
- , optSmart = False
- , optOldDashes = False
- , optHtml5 = False
- , optHtmlQTags = False
- , optHighlight = True
- , optHighlightStyle = pygments
- , optChapters = False
- , optHTMLMathMethod = PlainMath
- , optReferenceODT = Nothing
- , optReferenceDocx = Nothing
- , optEpubStylesheet = Nothing
- , optEpubMetadata = ""
- , optEpubFonts = []
- , optEpubChapterLevel = 1
- , optTOCDepth = 3
- , optDumpArgs = False
- , optIgnoreArgs = False
- , optReferenceLinks = False
- , optWrapText = True
- , optColumns = 72
- , optPlugins = []
- , optEmailObfuscation = JavascriptObfuscation
- , optIdentifierPrefix = ""
- , optIndentedCodeClasses = []
- , optDataDir = Nothing
- , optCiteMethod = Citeproc
- , optBibliography = []
- , optCslFile = Nothing
- , optAbbrevsFile = Nothing
- , optListings = False
- , optLaTeXEngine = "pdflatex"
- , optSlideLevel = Nothing
- , optSetextHeaders = True
- , optAscii = False
- , optTeXLigatures = True
+ { optTabStop = 4
+ , optPreserveTabs = False
+ , optStandalone = False
+ , optReader = "" -- null for default reader
+ , optWriter = "" -- null for default writer
+ , optParseRaw = False
+ , optTableOfContents = False
+ , optTransforms = []
+ , optTemplate = Nothing
+ , optVariables = []
+ , optOutputFile = "-" -- "-" means stdout
+ , optNumberSections = False
+ , optSectionDivs = False
+ , optIncremental = False
+ , optSelfContained = False
+ , optSmart = False
+ , optOldDashes = False
+ , optHtml5 = False
+ , optHtmlQTags = False
+ , optHighlight = True
+ , optHighlightStyle = pygments
+ , optChapters = False
+ , optHTMLMathMethod = PlainMath
+ , optReferenceODT = Nothing
+ , optReferenceDocx = Nothing
+ , optEpubStylesheet = Nothing
+ , optEpubMetadata = ""
+ , optEpubFonts = []
+ , optEpubChapterLevel = 1
+ , optTOCDepth = 3
+ , optDumpArgs = False
+ , optIgnoreArgs = False
+ , optReferenceLinks = False
+ , optWrapText = True
+ , optColumns = 72
+ , optPlugins = []
+ , optEmailObfuscation = JavascriptObfuscation
+ , optIdentifierPrefix = ""
+ , optIndentedCodeClasses = []
+ , optDataDir = Nothing
+ , optCiteMethod = Citeproc
+ , optBibliography = []
+ , optCslFile = Nothing
+ , optAbbrevsFile = Nothing
+ , optListings = False
+ , optLaTeXEngine = "pdflatex"
+ , optSlideLevel = Nothing
+ , optSetextHeaders = True
+ , optAscii = False
+ , optTeXLigatures = True
+ , optDefaultImageExtension = ""
}
-- | A list of functions, each transforming the options data structure
@@ -495,6 +497,12 @@ options =
(\opt -> return opt { optSectionDivs = True }))
"" -- "Put sections in div tags in HTML"
+ , Option "" ["default-image-extension"]
+ (ReqArg
+ (\arg opt -> return opt { optDefaultImageExtension = arg })
+ "extension")
+ "" -- "Default extension for extensionless images"
+
, Option "" ["email-obfuscation"]
(ReqArg
(\arg opt -> do
@@ -806,55 +814,56 @@ main = do
-- thread option data structure through all supplied option actions
opts <- foldl (>>=) (return defaultOpts') actions
- let Opt { optTabStop = tabStop
- , optPreserveTabs = preserveTabs
- , optStandalone = standalone
- , optReader = readerName
- , optWriter = writerName
- , optParseRaw = parseRaw
- , optVariables = variables
- , optTableOfContents = toc
- , optTransforms = transforms
- , optTemplate = templatePath
- , optOutputFile = outputFile
- , optNumberSections = numberSections
- , optSectionDivs = sectionDivs
- , optIncremental = incremental
- , optSelfContained = selfContained
- , optSmart = smart
- , optOldDashes = oldDashes
- , optHtml5 = html5
- , optHtmlQTags = htmlQTags
- , optHighlight = highlight
- , optHighlightStyle = highlightStyle
- , optChapters = chapters
- , optHTMLMathMethod = mathMethod
- , optReferenceODT = referenceODT
- , optReferenceDocx = referenceDocx
- , optEpubStylesheet = epubStylesheet
- , optEpubMetadata = epubMetadata
- , optEpubFonts = epubFonts
- , optEpubChapterLevel = epubChapterLevel
- , optTOCDepth = epubTOCDepth
- , optDumpArgs = dumpArgs
- , optIgnoreArgs = ignoreArgs
- , optReferenceLinks = referenceLinks
- , optWrapText = wrap
- , optColumns = columns
- , optEmailObfuscation = obfuscationMethod
- , optIdentifierPrefix = idPrefix
- , optIndentedCodeClasses = codeBlockClasses
- , optDataDir = mbDataDir
- , optBibliography = reffiles
- , optCslFile = mbCsl
- , optAbbrevsFile = cslabbrevs
- , optCiteMethod = citeMethod
- , optListings = listings
- , optLaTeXEngine = latexEngine
- , optSlideLevel = slideLevel
- , optSetextHeaders = setextHeaders
- , optAscii = ascii
- , optTeXLigatures = texLigatures
+ let Opt { optTabStop = tabStop
+ , optPreserveTabs = preserveTabs
+ , optStandalone = standalone
+ , optReader = readerName
+ , optWriter = writerName
+ , optParseRaw = parseRaw
+ , optVariables = variables
+ , optTableOfContents = toc
+ , optTransforms = transforms
+ , optTemplate = templatePath
+ , optOutputFile = outputFile
+ , optNumberSections = numberSections
+ , optSectionDivs = sectionDivs
+ , optIncremental = incremental
+ , optSelfContained = selfContained
+ , optSmart = smart
+ , optOldDashes = oldDashes
+ , optHtml5 = html5
+ , optHtmlQTags = htmlQTags
+ , optHighlight = highlight
+ , optHighlightStyle = highlightStyle
+ , optChapters = chapters
+ , optHTMLMathMethod = mathMethod
+ , optReferenceODT = referenceODT
+ , optReferenceDocx = referenceDocx
+ , optEpubStylesheet = epubStylesheet
+ , optEpubMetadata = epubMetadata
+ , optEpubFonts = epubFonts
+ , optEpubChapterLevel = epubChapterLevel
+ , optTOCDepth = epubTOCDepth
+ , optDumpArgs = dumpArgs
+ , optIgnoreArgs = ignoreArgs
+ , optReferenceLinks = referenceLinks
+ , optWrapText = wrap
+ , optColumns = columns
+ , optEmailObfuscation = obfuscationMethod
+ , optIdentifierPrefix = idPrefix
+ , optIndentedCodeClasses = codeBlockClasses
+ , optDataDir = mbDataDir
+ , optBibliography = reffiles
+ , optCslFile = mbCsl
+ , optAbbrevsFile = cslabbrevs
+ , optCiteMethod = citeMethod
+ , optListings = listings
+ , optLaTeXEngine = latexEngine
+ , optSlideLevel = slideLevel
+ , optSetextHeaders = setextHeaders
+ , optAscii = ascii
+ , optTeXLigatures = texLigatures
+ , optDefaultImageExtension = defaultImageExtension
} = opts
when dumpArgs $
@@ -996,6 +1005,7 @@ main = do
, readerCitationStyle = mbsty
, readerIndentedCodeClasses = codeBlockClasses
, readerApplyMacros = not laTeXOutput
+ , readerDefaultImageExtension = defaultImageExtension
}
let writerOptions = def { writerStandalone = standalone',
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs
index f67debf97..1ba8a6dd6 100644
--- a/src/Text/Pandoc/Options.hs
+++ b/src/Text/Pandoc/Options.hs
@@ -204,22 +204,24 @@ data ReaderOptions = ReaderOptions{
, readerApplyMacros :: Bool -- ^ Apply macros to TeX math
, readerIndentedCodeClasses :: [String] -- ^ Default classes for
-- indented code blocks
+ , readerDefaultImageExtension :: String -- ^ Default extension for images
} deriving (Show, Read)
instance Default ReaderOptions
where def = ReaderOptions{
- readerExtensions = pandocExtensions
- , readerSmart = False
- , readerStrict = False
- , readerStandalone = False
- , readerParseRaw = False
- , readerColumns = 80
- , readerTabStop = 4
- , readerOldDashes = False
- , readerReferences = []
- , readerCitationStyle = Nothing
- , readerApplyMacros = True
- , readerIndentedCodeClasses = []
+ readerExtensions = pandocExtensions
+ , readerSmart = False
+ , readerStrict = False
+ , readerStandalone = False
+ , readerParseRaw = False
+ , readerColumns = 80
+ , readerTabStop = 4
+ , readerOldDashes = False
+ , readerReferences = []
+ , readerCitationStyle = Nothing
+ , readerApplyMacros = True
+ , readerIndentedCodeClasses = []
+ , readerDefaultImageExtension = ""
}
--
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index dc30e17ed..6b144f35e 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -51,6 +51,7 @@ import qualified Text.CSL as CSL
import Data.Monoid (mconcat, mempty)
import Control.Applicative ((<$>), (<*), (*>), (<$))
import Control.Monad
+import System.FilePath (takeExtension, addExtension)
import Text.HTML.TagSoup
import Text.HTML.TagSoup.Match (tagOpen)
import qualified Data.Set as Set
@@ -1561,7 +1562,11 @@ image :: MarkdownParser (F Inlines)
image = try $ do
char '!'
(lab,raw) <- reference
- regLink B.image lab <|> referenceLink B.image (lab,raw)
+ defaultExt <- getOption readerDefaultImageExtension
+ let constructor src = case takeExtension src of
+ "" -> B.image (addExtension src defaultExt)
+ _ -> B.image src
+ regLink constructor lab <|> referenceLink constructor (lab,raw)
note :: MarkdownParser (F Inlines)
note = try $ do