Added --default-image-extension and readerDefaultImageExtension.

Note: Currently this only affects the markdown reader.
This commit is contained in:
John MacFarlane 2013-02-05 20:08:00 -08:00
parent 1aa74199cf
commit c5f1a8ad2d
4 changed files with 134 additions and 112 deletions

5
README
View file

@ -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.

View file

@ -137,6 +137,7 @@ 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.
@ -192,6 +193,7 @@ defaultOpts = Opt
, 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
@ -855,6 +863,7 @@ main = do
, 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',

View file

@ -204,6 +204,7 @@ 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
@ -220,6 +221,7 @@ instance Default ReaderOptions
, readerCitationStyle = Nothing
, readerApplyMacros = True
, readerIndentedCodeClasses = []
, readerDefaultImageExtension = ""
}
--

View file

@ -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