Added writerTeXLigatures to WriterOptions, --no-tex-ligatures
option.
This is useful for those who want to use advanced OpenType features with xelatex/lualatex.
This commit is contained in:
parent
1aec24a169
commit
5f889b9396
6 changed files with 65 additions and 37 deletions
13
README
13
README
|
@ -213,7 +213,7 @@ Reader options
|
||||||
abbreviations, such as "Mr." (Note: This option is significant only when
|
abbreviations, such as "Mr." (Note: This option is significant only when
|
||||||
the input format is `markdown` or `textile`. It is selected automatically
|
the input format is `markdown` or `textile`. It is selected automatically
|
||||||
when the input format is `textile` or the output format is `latex` or
|
when the input format is `textile` or the output format is `latex` or
|
||||||
`context`.)
|
`context`, unless `--no-tex-ligatures` is used.)
|
||||||
|
|
||||||
`--old-dashes`
|
`--old-dashes`
|
||||||
: Selects the pandoc <= 1.8.2.1 behavior for parsing smart dashes: `-` before
|
: Selects the pandoc <= 1.8.2.1 behavior for parsing smart dashes: `-` before
|
||||||
|
@ -358,6 +358,17 @@ Options affecting specific writers
|
||||||
: Number section headings in LaTeX, ConTeXt, or HTML output.
|
: Number section headings in LaTeX, ConTeXt, or HTML output.
|
||||||
By default, sections are not numbered.
|
By default, sections are not numbered.
|
||||||
|
|
||||||
|
`--no-tex-ligatures`
|
||||||
|
: Do not convert quotation marks, apostrophes, and dashes to
|
||||||
|
the TeX ligatures when writing LaTeX or ConTeXt. Instead, just
|
||||||
|
use literal unicode characters. This is needed for using advanced
|
||||||
|
OpenType features with XeLaTeX and LuaLaTeX. Note: normally
|
||||||
|
`--smart` is selected automatically for LaTeX and ConTeXt
|
||||||
|
output, but it must be specified explicitly if `--no-tex-ligatures`
|
||||||
|
is selected. If you use literal curly quotes, dashes, and ellipses
|
||||||
|
in your source, then you may want to use `--no-tex-ligatures`
|
||||||
|
without `--smart`.
|
||||||
|
|
||||||
`--listings`
|
`--listings`
|
||||||
: Use listings package for LaTeX code blocks
|
: Use listings package for LaTeX code blocks
|
||||||
|
|
||||||
|
|
|
@ -43,6 +43,8 @@ pandoc (1.9.3)
|
||||||
|
|
||||||
* LaTeX writer:
|
* LaTeX writer:
|
||||||
|
|
||||||
|
+ Added `--no-tex-ligatures` option to avoid replacing
|
||||||
|
quotation marks and dashes with TeX ligatures.
|
||||||
+ Use `fixltx2e` package to provide '\textsubscript'.
|
+ Use `fixltx2e` package to provide '\textsubscript'.
|
||||||
+ Improve spacing around LaTeX block environments:
|
+ Improve spacing around LaTeX block environments:
|
||||||
quote, verbatim, itemize, description, enumerate.
|
quote, verbatim, itemize, description, enumerate.
|
||||||
|
|
|
@ -520,6 +520,7 @@ data WriterOptions = WriterOptions
|
||||||
, writerHighlight :: Bool -- ^ Highlight source code
|
, writerHighlight :: Bool -- ^ Highlight source code
|
||||||
, writerHighlightStyle :: Style -- ^ Style to use for highlighting
|
, writerHighlightStyle :: Style -- ^ Style to use for highlighting
|
||||||
, writerSetextHeaders :: Bool -- ^ Use setext headers for levels 1-2 in markdown
|
, writerSetextHeaders :: Bool -- ^ Use setext headers for levels 1-2 in markdown
|
||||||
|
, writerTeXLigatures :: Bool -- ^ Use tex ligatures quotes, dashes in latex
|
||||||
} deriving Show
|
} deriving Show
|
||||||
|
|
||||||
{-# DEPRECATED writerXeTeX "writerXeTeX no longer does anything" #-}
|
{-# DEPRECATED writerXeTeX "writerXeTeX no longer does anything" #-}
|
||||||
|
@ -558,6 +559,7 @@ defaultWriterOptions =
|
||||||
, writerHighlight = False
|
, writerHighlight = False
|
||||||
, writerHighlightStyle = pygments
|
, writerHighlightStyle = pygments
|
||||||
, writerSetextHeaders = True
|
, writerSetextHeaders = True
|
||||||
|
, writerTeXLigatures = True
|
||||||
}
|
}
|
||||||
|
|
||||||
--
|
--
|
||||||
|
|
|
@ -86,8 +86,9 @@ pandocToConTeXt options (Pandoc (Meta title authors date) blocks) = do
|
||||||
|
|
||||||
-- escape things as needed for ConTeXt
|
-- escape things as needed for ConTeXt
|
||||||
|
|
||||||
escapeCharForConTeXt :: Char -> String
|
escapeCharForConTeXt :: WriterOptions -> Char -> String
|
||||||
escapeCharForConTeXt ch =
|
escapeCharForConTeXt opts ch =
|
||||||
|
let ligatures = writerTeXLigatures opts in
|
||||||
case ch of
|
case ch of
|
||||||
'{' -> "\\letteropenbrace{}"
|
'{' -> "\\letteropenbrace{}"
|
||||||
'}' -> "\\letterclosebrace{}"
|
'}' -> "\\letterclosebrace{}"
|
||||||
|
@ -105,15 +106,15 @@ escapeCharForConTeXt ch =
|
||||||
']' -> "{]}"
|
']' -> "{]}"
|
||||||
'_' -> "\\letterunderscore{}"
|
'_' -> "\\letterunderscore{}"
|
||||||
'\160' -> "~"
|
'\160' -> "~"
|
||||||
'\x2014' -> "---"
|
'\x2014' | ligatures -> "---"
|
||||||
'\x2013' -> "--"
|
'\x2013' | ligatures -> "--"
|
||||||
'\x2019' -> "'"
|
'\x2019' | ligatures -> "'"
|
||||||
'\x2026' -> "\\ldots{}"
|
'\x2026' -> "\\ldots{}"
|
||||||
x -> [x]
|
x -> [x]
|
||||||
|
|
||||||
-- | Escape string for ConTeXt
|
-- | Escape string for ConTeXt
|
||||||
stringToConTeXt :: String -> String
|
stringToConTeXt :: WriterOptions -> String -> String
|
||||||
stringToConTeXt = concatMap escapeCharForConTeXt
|
stringToConTeXt opts = concatMap (escapeCharForConTeXt opts)
|
||||||
|
|
||||||
-- | Convert Elements to ConTeXt
|
-- | Convert Elements to ConTeXt
|
||||||
elementToConTeXt :: WriterOptions -> Element -> State WriterState Doc
|
elementToConTeXt :: WriterOptions -> Element -> State WriterState Doc
|
||||||
|
@ -254,8 +255,9 @@ inlineToConTeXt (SmallCaps lst) = do
|
||||||
return $ braces $ "\\sc " <> contents
|
return $ braces $ "\\sc " <> contents
|
||||||
inlineToConTeXt (Code _ str) | not ('{' `elem` str || '}' `elem` str) =
|
inlineToConTeXt (Code _ str) | not ('{' `elem` str || '}' `elem` str) =
|
||||||
return $ "\\type" <> braces (text str)
|
return $ "\\type" <> braces (text str)
|
||||||
inlineToConTeXt (Code _ str) =
|
inlineToConTeXt (Code _ str) = do
|
||||||
return $ "\\mono" <> braces (text $ stringToConTeXt str)
|
opts <- gets stOptions
|
||||||
|
return $ "\\mono" <> braces (text $ stringToConTeXt opts str)
|
||||||
inlineToConTeXt (Quoted SingleQuote lst) = do
|
inlineToConTeXt (Quoted SingleQuote lst) = do
|
||||||
contents <- inlineListToConTeXt lst
|
contents <- inlineListToConTeXt lst
|
||||||
return $ "\\quote" <> braces contents
|
return $ "\\quote" <> braces contents
|
||||||
|
@ -263,7 +265,9 @@ inlineToConTeXt (Quoted DoubleQuote lst) = do
|
||||||
contents <- inlineListToConTeXt lst
|
contents <- inlineListToConTeXt lst
|
||||||
return $ "\\quotation" <> braces contents
|
return $ "\\quotation" <> braces contents
|
||||||
inlineToConTeXt (Cite _ lst) = inlineListToConTeXt lst
|
inlineToConTeXt (Cite _ lst) = inlineListToConTeXt lst
|
||||||
inlineToConTeXt (Str str) = return $ text $ stringToConTeXt str
|
inlineToConTeXt (Str str) = do
|
||||||
|
opts <- gets stOptions
|
||||||
|
return $ text $ stringToConTeXt opts str
|
||||||
inlineToConTeXt (Math InlineMath str) =
|
inlineToConTeXt (Math InlineMath str) =
|
||||||
return $ char '$' <> text str <> char '$'
|
return $ char '$' <> text str <> char '$'
|
||||||
inlineToConTeXt (Math DisplayMath str) =
|
inlineToConTeXt (Math DisplayMath str) =
|
||||||
|
|
|
@ -174,9 +174,11 @@ elementToLaTeX opts (Sec level _ id' title' elements) = do
|
||||||
|
|
||||||
-- escape things as needed for LaTeX
|
-- escape things as needed for LaTeX
|
||||||
stringToLaTeX :: Bool -> String -> State WriterState String
|
stringToLaTeX :: Bool -> String -> State WriterState String
|
||||||
stringToLaTeX _ [] = return ""
|
stringToLaTeX _ [] = return ""
|
||||||
stringToLaTeX isUrl (x:xs) = do
|
stringToLaTeX isUrl (x:xs) = do
|
||||||
|
opts <- gets stOptions
|
||||||
rest <- stringToLaTeX isUrl xs
|
rest <- stringToLaTeX isUrl xs
|
||||||
|
let ligatures = writerTeXLigatures opts
|
||||||
when (x == '€') $
|
when (x == '€') $
|
||||||
modify $ \st -> st{ stUsesEuro = True }
|
modify $ \st -> st{ stUsesEuro = True }
|
||||||
return $
|
return $
|
||||||
|
@ -201,13 +203,13 @@ stringToLaTeX isUrl (x:xs) = do
|
||||||
'[' -> "{[}" ++ rest -- to avoid interpretation as
|
'[' -> "{[}" ++ rest -- to avoid interpretation as
|
||||||
']' -> "{]}" ++ rest -- optional arguments
|
']' -> "{]}" ++ rest -- optional arguments
|
||||||
'\160' -> "~" ++ rest
|
'\160' -> "~" ++ rest
|
||||||
'\x2018' -> "`" ++ rest
|
|
||||||
'\x2019' -> "'" ++ rest
|
|
||||||
'\x201C' -> "``" ++ rest
|
|
||||||
'\x201D' -> "''" ++ rest
|
|
||||||
'\x2026' -> "\\ldots{}" ++ rest
|
'\x2026' -> "\\ldots{}" ++ rest
|
||||||
'\x2014' -> "---" ++ rest
|
'\x2018' | ligatures -> "`" ++ rest
|
||||||
'\x2013' -> "--" ++ rest
|
'\x2019' | ligatures -> "'" ++ rest
|
||||||
|
'\x201C' | ligatures -> "``" ++ rest
|
||||||
|
'\x201D' | ligatures -> "''" ++ rest
|
||||||
|
'\x2014' | ligatures -> "---" ++ rest
|
||||||
|
'\x2013' | ligatures -> "--" ++ rest
|
||||||
_ -> x : rest
|
_ -> x : rest
|
||||||
|
|
||||||
-- | Puts contents into LaTeX command.
|
-- | Puts contents into LaTeX command.
|
||||||
|
@ -536,10 +538,11 @@ inlineToLaTeX (Code (_,classes,_) str) = do
|
||||||
Just h -> modify (\st -> st{ stHighlighting = True }) >>
|
Just h -> modify (\st -> st{ stHighlighting = True }) >>
|
||||||
return (text h)
|
return (text h)
|
||||||
rawCode = liftM (text . (\s -> "\\texttt{" ++ s ++ "}"))
|
rawCode = liftM (text . (\s -> "\\texttt{" ++ s ++ "}"))
|
||||||
$ stringToLaTeX False str
|
$ stringToLaTeX False str
|
||||||
inlineToLaTeX (Quoted SingleQuote lst) = do
|
inlineToLaTeX (Quoted qt lst) = do
|
||||||
contents <- inlineListToLaTeX lst
|
contents <- inlineListToLaTeX lst
|
||||||
csquotes <- liftM stCsquotes get
|
csquotes <- liftM stCsquotes get
|
||||||
|
opts <- gets stOptions
|
||||||
if csquotes
|
if csquotes
|
||||||
then return $ "\\enquote" <> braces contents
|
then return $ "\\enquote" <> braces contents
|
||||||
else do
|
else do
|
||||||
|
@ -549,20 +552,16 @@ inlineToLaTeX (Quoted SingleQuote lst) = do
|
||||||
let s2 = if (not (null lst)) && (isQuoted (last lst))
|
let s2 = if (not (null lst)) && (isQuoted (last lst))
|
||||||
then "\\,"
|
then "\\,"
|
||||||
else empty
|
else empty
|
||||||
return $ char '`' <> s1 <> contents <> s2 <> char '\''
|
let inner = s1 <> contents <> s2
|
||||||
inlineToLaTeX (Quoted DoubleQuote lst) = do
|
return $ case qt of
|
||||||
contents <- inlineListToLaTeX lst
|
DoubleQuote ->
|
||||||
csquotes <- liftM stCsquotes get
|
if writerTeXLigatures opts
|
||||||
if csquotes
|
then text "``" <> inner <> text "''"
|
||||||
then return $ "\\enquote" <> braces contents
|
else char '\x201C' <> inner <> char '\x201D'
|
||||||
else do
|
SingleQuote ->
|
||||||
let s1 = if (not (null lst)) && (isQuoted (head lst))
|
if writerTeXLigatures opts
|
||||||
then "\\,"
|
then char '`' <> inner <> char '\''
|
||||||
else empty
|
else char '\x2018' <> inner <> char '\x2019'
|
||||||
let s2 = if (not (null lst)) && (isQuoted (last lst))
|
|
||||||
then "\\,"
|
|
||||||
else empty
|
|
||||||
return $ "``" <> s1 <> contents <> s2 <> "''"
|
|
||||||
inlineToLaTeX (Str str) = liftM text $ stringToLaTeX False str
|
inlineToLaTeX (Str str) = liftM text $ stringToLaTeX False str
|
||||||
inlineToLaTeX (Math InlineMath str) = return $ char '$' <> text str <> char '$'
|
inlineToLaTeX (Math InlineMath str) = return $ char '$' <> text str <> char '$'
|
||||||
inlineToLaTeX (Math DisplayMath str) = return $ "\\[" <> text str <> "\\]"
|
inlineToLaTeX (Math DisplayMath str) = return $ "\\[" <> text str <> "\\]"
|
||||||
|
|
|
@ -135,6 +135,7 @@ data Opt = Opt
|
||||||
, optSlideLevel :: Maybe Int -- ^ Header level that creates slides
|
, optSlideLevel :: Maybe Int -- ^ Header level that creates slides
|
||||||
, 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
|
||||||
}
|
}
|
||||||
|
|
||||||
-- | Defaults for command-line options.
|
-- | Defaults for command-line options.
|
||||||
|
@ -187,6 +188,7 @@ defaultOpts = Opt
|
||||||
, optSlideLevel = Nothing
|
, optSlideLevel = Nothing
|
||||||
, optSetextHeaders = True
|
, optSetextHeaders = True
|
||||||
, optAscii = False
|
, optAscii = False
|
||||||
|
, optTeXLigatures = True
|
||||||
}
|
}
|
||||||
|
|
||||||
-- | A list of functions, each transforming the options data structure
|
-- | A list of functions, each transforming the options data structure
|
||||||
|
@ -438,6 +440,11 @@ options =
|
||||||
(\opt -> return opt { optNumberSections = True }))
|
(\opt -> return opt { optNumberSections = True }))
|
||||||
"" -- "Number sections in LaTeX"
|
"" -- "Number sections in LaTeX"
|
||||||
|
|
||||||
|
, Option "" ["no-tex-ligatures"]
|
||||||
|
(NoArg
|
||||||
|
(\opt -> return opt { optTeXLigatures = False }))
|
||||||
|
"" -- "Don't use tex ligatures for quotes, dashes"
|
||||||
|
|
||||||
, Option "" ["listings"]
|
, Option "" ["listings"]
|
||||||
(NoArg
|
(NoArg
|
||||||
(\opt -> return opt { optListings = True }))
|
(\opt -> return opt { optListings = True }))
|
||||||
|
@ -804,6 +811,7 @@ main = do
|
||||||
, optSlideLevel = slideLevel
|
, optSlideLevel = slideLevel
|
||||||
, optSetextHeaders = setextHeaders
|
, optSetextHeaders = setextHeaders
|
||||||
, optAscii = ascii
|
, optAscii = ascii
|
||||||
|
, optTeXLigatures = texLigatures
|
||||||
} = opts
|
} = opts
|
||||||
|
|
||||||
when dumpArgs $
|
when dumpArgs $
|
||||||
|
@ -918,7 +926,8 @@ main = do
|
||||||
lhsExtension sources,
|
lhsExtension sources,
|
||||||
stateStandalone = standalone',
|
stateStandalone = standalone',
|
||||||
stateCitations = map CSL.refId refs,
|
stateCitations = map CSL.refId refs,
|
||||||
stateSmart = smart || laTeXOutput || writerName' == "context",
|
stateSmart = smart || (texLigatures &&
|
||||||
|
(laTeXOutput || writerName' == "context")),
|
||||||
stateOldDashes = oldDashes,
|
stateOldDashes = oldDashes,
|
||||||
stateColumns = columns,
|
stateColumns = columns,
|
||||||
stateStrict = strict,
|
stateStrict = strict,
|
||||||
|
@ -961,7 +970,8 @@ main = do
|
||||||
writerSlideLevel = slideLevel,
|
writerSlideLevel = slideLevel,
|
||||||
writerHighlight = highlight,
|
writerHighlight = highlight,
|
||||||
writerHighlightStyle = highlightStyle,
|
writerHighlightStyle = highlightStyle,
|
||||||
writerSetextHeaders = setextHeaders
|
writerSetextHeaders = setextHeaders,
|
||||||
|
writerTeXLigatures = texLigatures
|
||||||
}
|
}
|
||||||
|
|
||||||
when (writerName' `elem` nonTextFormats&& outputFile == "-") $
|
when (writerName' `elem` nonTextFormats&& outputFile == "-") $
|
||||||
|
|
Loading…
Reference in a new issue