Added --default-image-extension
and readerDefaultImageExtension
.
Note: Currently this only affects the markdown reader.
This commit is contained in:
parent
1aa74199cf
commit
c5f1a8ad2d
4 changed files with 134 additions and 112 deletions
5
README
5
README
|
@ -243,6 +243,11 @@ Reader options
|
||||||
`perl,numberLines` or `haskell`. Multiple classes may be separated
|
`perl,numberLines` or `haskell`. Multiple classes may be separated
|
||||||
by spaces or commas.
|
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`
|
||||||
: Normalize the document after reading: merge adjacent
|
: Normalize the document after reading: merge adjacent
|
||||||
`Str` or `Emph` elements, for example, and remove repeated `Space`s.
|
`Str` or `Emph` elements, for example, and remove repeated `Space`s.
|
||||||
|
|
10
pandoc.hs
10
pandoc.hs
|
@ -137,6 +137,7 @@ data Opt = Opt
|
||||||
, optSetextHeaders :: Bool -- ^ Use atx headers for markdown level 1-2
|
, optSetextHeaders :: Bool -- ^ Use atx headers for markdown level 1-2
|
||||||
, optAscii :: Bool -- ^ Use ascii characters only in html
|
, optAscii :: Bool -- ^ Use ascii characters only in html
|
||||||
, optTeXLigatures :: Bool -- ^ Use TeX ligatures for quotes/dashes
|
, optTeXLigatures :: Bool -- ^ Use TeX ligatures for quotes/dashes
|
||||||
|
, optDefaultImageExtension :: String -- ^ Default image extension
|
||||||
}
|
}
|
||||||
|
|
||||||
-- | Defaults for command-line options.
|
-- | Defaults for command-line options.
|
||||||
|
@ -192,6 +193,7 @@ defaultOpts = Opt
|
||||||
, optSetextHeaders = True
|
, optSetextHeaders = True
|
||||||
, optAscii = False
|
, optAscii = False
|
||||||
, optTeXLigatures = True
|
, optTeXLigatures = True
|
||||||
|
, optDefaultImageExtension = ""
|
||||||
}
|
}
|
||||||
|
|
||||||
-- | A list of functions, each transforming the options data structure
|
-- | A list of functions, each transforming the options data structure
|
||||||
|
@ -495,6 +497,12 @@ options =
|
||||||
(\opt -> return opt { optSectionDivs = True }))
|
(\opt -> return opt { optSectionDivs = True }))
|
||||||
"" -- "Put sections in div tags in HTML"
|
"" -- "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"]
|
, Option "" ["email-obfuscation"]
|
||||||
(ReqArg
|
(ReqArg
|
||||||
(\arg opt -> do
|
(\arg opt -> do
|
||||||
|
@ -855,6 +863,7 @@ main = do
|
||||||
, optSetextHeaders = setextHeaders
|
, optSetextHeaders = setextHeaders
|
||||||
, optAscii = ascii
|
, optAscii = ascii
|
||||||
, optTeXLigatures = texLigatures
|
, optTeXLigatures = texLigatures
|
||||||
|
, optDefaultImageExtension = defaultImageExtension
|
||||||
} = opts
|
} = opts
|
||||||
|
|
||||||
when dumpArgs $
|
when dumpArgs $
|
||||||
|
@ -996,6 +1005,7 @@ main = do
|
||||||
, readerCitationStyle = mbsty
|
, readerCitationStyle = mbsty
|
||||||
, readerIndentedCodeClasses = codeBlockClasses
|
, readerIndentedCodeClasses = codeBlockClasses
|
||||||
, readerApplyMacros = not laTeXOutput
|
, readerApplyMacros = not laTeXOutput
|
||||||
|
, readerDefaultImageExtension = defaultImageExtension
|
||||||
}
|
}
|
||||||
|
|
||||||
let writerOptions = def { writerStandalone = standalone',
|
let writerOptions = def { writerStandalone = standalone',
|
||||||
|
|
|
@ -204,6 +204,7 @@ data ReaderOptions = ReaderOptions{
|
||||||
, readerApplyMacros :: Bool -- ^ Apply macros to TeX math
|
, readerApplyMacros :: Bool -- ^ Apply macros to TeX math
|
||||||
, readerIndentedCodeClasses :: [String] -- ^ Default classes for
|
, readerIndentedCodeClasses :: [String] -- ^ Default classes for
|
||||||
-- indented code blocks
|
-- indented code blocks
|
||||||
|
, readerDefaultImageExtension :: String -- ^ Default extension for images
|
||||||
} deriving (Show, Read)
|
} deriving (Show, Read)
|
||||||
|
|
||||||
instance Default ReaderOptions
|
instance Default ReaderOptions
|
||||||
|
@ -220,6 +221,7 @@ instance Default ReaderOptions
|
||||||
, readerCitationStyle = Nothing
|
, readerCitationStyle = Nothing
|
||||||
, readerApplyMacros = True
|
, readerApplyMacros = True
|
||||||
, readerIndentedCodeClasses = []
|
, readerIndentedCodeClasses = []
|
||||||
|
, readerDefaultImageExtension = ""
|
||||||
}
|
}
|
||||||
|
|
||||||
--
|
--
|
||||||
|
|
|
@ -51,6 +51,7 @@ import qualified Text.CSL as CSL
|
||||||
import Data.Monoid (mconcat, mempty)
|
import Data.Monoid (mconcat, mempty)
|
||||||
import Control.Applicative ((<$>), (<*), (*>), (<$))
|
import Control.Applicative ((<$>), (<*), (*>), (<$))
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
|
import System.FilePath (takeExtension, addExtension)
|
||||||
import Text.HTML.TagSoup
|
import Text.HTML.TagSoup
|
||||||
import Text.HTML.TagSoup.Match (tagOpen)
|
import Text.HTML.TagSoup.Match (tagOpen)
|
||||||
import qualified Data.Set as Set
|
import qualified Data.Set as Set
|
||||||
|
@ -1561,7 +1562,11 @@ image :: MarkdownParser (F Inlines)
|
||||||
image = try $ do
|
image = try $ do
|
||||||
char '!'
|
char '!'
|
||||||
(lab,raw) <- reference
|
(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 :: MarkdownParser (F Inlines)
|
||||||
note = try $ do
|
note = try $ do
|
||||||
|
|
Loading…
Reference in a new issue