+ Added support for superscript, subscript, and
strikeout to all writers. (Thanks to Bradley Kuhn for the patches for strikeout, here slightly modified.) + Refactored character escaping using the new functions escapeStringUsing and backslashEscapes. + Added state to LaTeX writer, which now keeps track of what packages need to be included in the preamble, based on the content of the document. (Thus, e.g., ulem is only required if you use strikeout.) git-svn-id: https://pandoc.googlecode.com/svn/trunk@755 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
parent
d03ec5a4a2
commit
6bb6dd2bfd
8 changed files with 260 additions and 178 deletions
|
@ -192,6 +192,15 @@ inlineToConTeXt (Emph lst) = do
|
||||||
inlineToConTeXt (Strong lst) = do
|
inlineToConTeXt (Strong lst) = do
|
||||||
contents <- inlineListToConTeXt lst
|
contents <- inlineListToConTeXt lst
|
||||||
return $ "{\\bf " ++ contents ++ "}"
|
return $ "{\\bf " ++ contents ++ "}"
|
||||||
|
inlineToConTeXt (Strikeout lst) = do
|
||||||
|
contents <- inlineListToConTeXt lst
|
||||||
|
return $ "\\overstrikes{" ++ contents ++ "}"
|
||||||
|
inlineToConTeXt (Superscript lst) = do
|
||||||
|
contents <- inlineListToConTeXt lst
|
||||||
|
return $ "\\high{" ++ contents ++ "}"
|
||||||
|
inlineToConTeXt (Subscript lst) = do
|
||||||
|
contents <- inlineListToConTeXt lst
|
||||||
|
return $ "\\low{" ++ contents ++ "}"
|
||||||
inlineToConTeXt (Code str) = return $ "\\type{" ++ str ++ "}"
|
inlineToConTeXt (Code str) = return $ "\\type{" ++ str ++ "}"
|
||||||
inlineToConTeXt (Quoted SingleQuote lst) = do
|
inlineToConTeXt (Quoted SingleQuote lst) = do
|
||||||
contents <- inlineListToConTeXt lst
|
contents <- inlineListToConTeXt lst
|
||||||
|
@ -206,7 +215,7 @@ inlineToConTeXt Ellipses = return "\\ldots{}"
|
||||||
inlineToConTeXt (Str str) = return $ stringToConTeXt str
|
inlineToConTeXt (Str str) = return $ stringToConTeXt str
|
||||||
inlineToConTeXt (TeX str) = return str
|
inlineToConTeXt (TeX str) = return str
|
||||||
inlineToConTeXt (HtmlInline str) = return ""
|
inlineToConTeXt (HtmlInline str) = return ""
|
||||||
inlineToConTeXt (LineBreak) = return "\\hfil\\break\n"
|
inlineToConTeXt (LineBreak) = return "\\crlf\n"
|
||||||
inlineToConTeXt Space = return " "
|
inlineToConTeXt Space = return " "
|
||||||
inlineToConTeXt (Link text (src, _)) = do
|
inlineToConTeXt (Link text (src, _)) = do
|
||||||
next <- get
|
next <- get
|
||||||
|
|
|
@ -233,6 +233,13 @@ inlineToDocbook opts (Emph lst) =
|
||||||
inlineToDocbook opts (Strong lst) =
|
inlineToDocbook opts (Strong lst) =
|
||||||
inTags False "emphasis" [("role", "strong")]
|
inTags False "emphasis" [("role", "strong")]
|
||||||
(inlinesToDocbook opts lst)
|
(inlinesToDocbook opts lst)
|
||||||
|
inlineToDocbook opts (Strikeout lst) =
|
||||||
|
inTags False "emphasis" [("role", "strikethrough")]
|
||||||
|
(inlinesToDocbook opts lst)
|
||||||
|
inlineToDocbook opts (Superscript lst) =
|
||||||
|
inTagsSimple "superscript" (inlinesToDocbook opts lst)
|
||||||
|
inlineToDocbook opts (Subscript lst) =
|
||||||
|
inTagsSimple "subscript" (inlinesToDocbook opts lst)
|
||||||
inlineToDocbook opts (Quoted _ lst) =
|
inlineToDocbook opts (Quoted _ lst) =
|
||||||
inTagsSimple "quote" (inlinesToDocbook opts lst)
|
inTagsSimple "quote" (inlinesToDocbook opts lst)
|
||||||
inlineToDocbook opts Apostrophe = text "'"
|
inlineToDocbook opts Apostrophe = text "'"
|
||||||
|
|
|
@ -66,6 +66,7 @@ writeHtml opts (Pandoc (Meta tit authors date) blocks) =
|
||||||
(if null date
|
(if null date
|
||||||
then noHtml
|
then noHtml
|
||||||
else meta ! [name "date", content date]) +++
|
else meta ! [name "date", content date]) +++
|
||||||
|
(style ! [thetype "text/css"] $ (stringToHtml ".strikeout { text-decoration: line-through; }")) +++
|
||||||
primHtml (writerHeader opts)
|
primHtml (writerHeader opts)
|
||||||
titleHeader = if (writerStandalone opts) && (not (null tit)) &&
|
titleHeader = if (writerStandalone opts) && (not (null tit)) &&
|
||||||
(not (writerS5 opts))
|
(not (writerS5 opts))
|
||||||
|
@ -179,23 +180,27 @@ inlineListToIdentifier [] = ""
|
||||||
inlineListToIdentifier (x:xs) =
|
inlineListToIdentifier (x:xs) =
|
||||||
xAsText ++ inlineListToIdentifier xs
|
xAsText ++ inlineListToIdentifier xs
|
||||||
where xAsText = case x of
|
where xAsText = case x of
|
||||||
Str s -> filter (\c -> (c == '-') || not (isPunctuation c)) $
|
Str s -> filter
|
||||||
concat $ intersperse "-" $ words $ map toLower s
|
(\c -> (c == '-') || not (isPunctuation c)) $
|
||||||
Emph lst -> inlineListToIdentifier lst
|
concat $ intersperse "-" $ words $ map toLower s
|
||||||
Strong lst -> inlineListToIdentifier lst
|
Emph lst -> inlineListToIdentifier lst
|
||||||
Quoted _ lst -> inlineListToIdentifier lst
|
Strikeout lst -> inlineListToIdentifier lst
|
||||||
Code s -> s
|
Superscript lst -> inlineListToIdentifier lst
|
||||||
Space -> "-"
|
Subscript lst -> inlineListToIdentifier lst
|
||||||
EmDash -> "-"
|
Strong lst -> inlineListToIdentifier lst
|
||||||
EnDash -> "-"
|
Quoted _ lst -> inlineListToIdentifier lst
|
||||||
Apostrophe -> ""
|
Code s -> s
|
||||||
Ellipses -> ""
|
Space -> "-"
|
||||||
LineBreak -> "-"
|
EmDash -> "-"
|
||||||
TeX _ -> ""
|
EnDash -> "-"
|
||||||
HtmlInline _ -> ""
|
Apostrophe -> ""
|
||||||
Link lst _ -> inlineListToIdentifier lst
|
Ellipses -> ""
|
||||||
Image lst _ -> inlineListToIdentifier lst
|
LineBreak -> "-"
|
||||||
Note _ -> ""
|
TeX _ -> ""
|
||||||
|
HtmlInline _ -> ""
|
||||||
|
Link lst _ -> inlineListToIdentifier lst
|
||||||
|
Image lst _ -> inlineListToIdentifier lst
|
||||||
|
Note _ -> ""
|
||||||
|
|
||||||
-- | Return unique identifiers for list of inline lists.
|
-- | Return unique identifiers for list of inline lists.
|
||||||
uniqueIdentifiers :: [[Inline]] -> [String]
|
uniqueIdentifiers :: [[Inline]] -> [String]
|
||||||
|
@ -326,6 +331,10 @@ inlineToHtml opts inline =
|
||||||
(Emph lst) -> inlineListToHtml opts lst >>= (return . emphasize)
|
(Emph lst) -> inlineListToHtml opts lst >>= (return . emphasize)
|
||||||
(Strong lst) -> inlineListToHtml opts lst >>= (return . strong)
|
(Strong lst) -> inlineListToHtml opts lst >>= (return . strong)
|
||||||
(Code str) -> return $ thecode << str
|
(Code str) -> return $ thecode << str
|
||||||
|
(Strikeout lst) -> inlineListToHtml opts lst >>=
|
||||||
|
(return . (thespan ! [theclass "strikeout"]))
|
||||||
|
(Superscript lst) -> inlineListToHtml opts lst >>= (return . sup)
|
||||||
|
(Subscript lst) -> inlineListToHtml opts lst >>= (return . sub)
|
||||||
(Quoted quoteType lst) ->
|
(Quoted quoteType lst) ->
|
||||||
let (leftQuote, rightQuote) = case quoteType of
|
let (leftQuote, rightQuote) = case quoteType of
|
||||||
SingleQuote -> (primHtmlChar "lsquo",
|
SingleQuote -> (primHtmlChar "lsquo",
|
||||||
|
|
|
@ -34,143 +34,164 @@ import Text.Pandoc.Definition
|
||||||
import Text.Pandoc.Shared
|
import Text.Pandoc.Shared
|
||||||
import Text.Printf ( printf )
|
import Text.Printf ( printf )
|
||||||
import Data.List ( (\\) )
|
import Data.List ( (\\) )
|
||||||
|
import qualified Data.Set as S
|
||||||
|
import Control.Monad.State
|
||||||
|
|
||||||
|
type WriterState = S.Set String -- set of strings to include in header
|
||||||
|
-- constructed based on content of document
|
||||||
|
|
||||||
|
-- | Add line to header.
|
||||||
|
addToHeader :: String -> State WriterState ()
|
||||||
|
addToHeader str = modify (S.insert str)
|
||||||
|
|
||||||
-- | Convert Pandoc to LaTeX.
|
-- | Convert Pandoc to LaTeX.
|
||||||
writeLaTeX :: WriterOptions -> Pandoc -> String
|
writeLaTeX :: WriterOptions -> Pandoc -> String
|
||||||
writeLaTeX options (Pandoc meta blocks) =
|
writeLaTeX options document =
|
||||||
let body = (writerIncludeBefore options) ++
|
evalState (pandocToLaTeX options document) S.empty
|
||||||
(concatMap blockToLaTeX blocks) ++
|
|
||||||
(writerIncludeAfter options)
|
pandocToLaTeX :: WriterOptions -> Pandoc -> State WriterState String
|
||||||
head = if writerStandalone options
|
pandocToLaTeX options (Pandoc meta blocks) = do
|
||||||
then latexHeader options meta
|
main <- blockListToLaTeX blocks
|
||||||
else ""
|
head <- if writerStandalone options
|
||||||
toc = if writerTableOfContents options
|
then latexHeader options meta
|
||||||
then "\\tableofcontents\n\n"
|
else return ""
|
||||||
else ""
|
let body = writerIncludeBefore options ++ main ++
|
||||||
foot = if writerStandalone options
|
writerIncludeAfter options
|
||||||
|
let toc = if writerTableOfContents options
|
||||||
|
then "\\tableofcontents\n\n"
|
||||||
|
else ""
|
||||||
|
let foot = if writerStandalone options
|
||||||
then "\n\\end{document}\n"
|
then "\n\\end{document}\n"
|
||||||
else ""
|
else ""
|
||||||
in head ++ toc ++ body ++ foot
|
return $ head ++ toc ++ body ++ foot
|
||||||
|
|
||||||
-- | Insert bibliographic information into LaTeX header.
|
-- | Insert bibliographic information into LaTeX header.
|
||||||
latexHeader :: WriterOptions -- ^ Options, including LaTeX header
|
latexHeader :: WriterOptions -- ^ Options, including LaTeX header
|
||||||
-> Meta -- ^ Meta with bibliographic information
|
-> Meta -- ^ Meta with bibliographic information
|
||||||
-> String
|
-> State WriterState String
|
||||||
latexHeader options (Meta title authors date) =
|
latexHeader options (Meta title authors date) = do
|
||||||
let titletext = if null title
|
titletext <- if null title
|
||||||
then ""
|
then return ""
|
||||||
else "\\title{" ++ inlineListToLaTeX title ++ "}\n"
|
else do title' <- inlineListToLaTeX title
|
||||||
authorstext = if null authors
|
return $ "\\title{" ++ title' ++ "}\n"
|
||||||
|
extras <- get
|
||||||
|
let authorstext = if null authors
|
||||||
then ""
|
then ""
|
||||||
else "\\author{" ++ (joinWithSep "\\\\"
|
else "\\author{" ++ (joinWithSep "\\\\"
|
||||||
(map stringToLaTeX authors)) ++ "}\n"
|
(map stringToLaTeX authors)) ++ "}\n"
|
||||||
datetext = if date == ""
|
let datetext = if date == ""
|
||||||
then ""
|
then ""
|
||||||
else "\\date{" ++ stringToLaTeX date ++ "}\n"
|
else "\\date{" ++ stringToLaTeX date ++ "}\n"
|
||||||
maketitle = if null title then "" else "\\maketitle\n\n"
|
let maketitle = if null title then "" else "\\maketitle\n\n"
|
||||||
secnumline = if (writerNumberSections options)
|
let secnumline = if (writerNumberSections options)
|
||||||
then ""
|
then ""
|
||||||
else "\\setcounter{secnumdepth}{0}\n"
|
else "\\setcounter{secnumdepth}{0}\n"
|
||||||
header = writerHeader options in
|
let baseHeader = writerHeader options
|
||||||
header ++ secnumline ++ titletext ++ authorstext ++ datetext ++
|
let header = baseHeader ++ (unlines $ S.toList extras)
|
||||||
"\\begin{document}\n" ++ maketitle
|
return $ header ++ secnumline ++ titletext ++ authorstext ++ datetext ++
|
||||||
|
"\\begin{document}\n" ++ maketitle
|
||||||
|
|
||||||
-- escape things as needed for LaTeX
|
-- escape things as needed for LaTeX
|
||||||
|
|
||||||
escapeCharForLaTeX :: Char -> String
|
|
||||||
escapeCharForLaTeX ch =
|
|
||||||
case ch of
|
|
||||||
'\\' -> "\\textbackslash{}"
|
|
||||||
'{' -> "\\{"
|
|
||||||
'}' -> "\\}"
|
|
||||||
'$' -> "\\$"
|
|
||||||
'%' -> "\\%"
|
|
||||||
'&' -> "\\&"
|
|
||||||
'~' -> "\\~"
|
|
||||||
'_' -> "\\_"
|
|
||||||
'#' -> "\\#"
|
|
||||||
'^' -> "\\^{}"
|
|
||||||
'|' -> "\\textbar{}"
|
|
||||||
'<' -> "\\textless{}"
|
|
||||||
'>' -> "\\textgreater{}"
|
|
||||||
x -> [x]
|
|
||||||
|
|
||||||
-- | Escape string for LaTeX
|
|
||||||
stringToLaTeX :: String -> String
|
stringToLaTeX :: String -> String
|
||||||
stringToLaTeX = concatMap escapeCharForLaTeX
|
stringToLaTeX = escapeStringUsing latexEscapes
|
||||||
|
where latexEscapes = [
|
||||||
|
('\\', "\\textbackslash{}"),
|
||||||
|
('{', "\\{"),
|
||||||
|
('}', "\\}"),
|
||||||
|
('$', "\\$"),
|
||||||
|
('%', "\\%"),
|
||||||
|
('&', "\\&"),
|
||||||
|
('~', "\\~"),
|
||||||
|
('_', "\\_"),
|
||||||
|
('#', "\\#"),
|
||||||
|
('^', "\\^{}"),
|
||||||
|
('|', "\\textbar{}"),
|
||||||
|
('<', "\\textless{}"),
|
||||||
|
('>', "\\textgreater{}")
|
||||||
|
]
|
||||||
|
|
||||||
-- | Remove all code elements from list of inline elements
|
-- | Remove all code elements from list of inline elements
|
||||||
-- (because it's illegal to have a \\verb inside a command argument)
|
-- (because it's illegal to have a \\verb inside a command argument)
|
||||||
deVerb :: [Inline] -> [Inline]
|
deVerb :: [Inline] -> [Inline]
|
||||||
deVerb [] = []
|
deVerb [] = []
|
||||||
deVerb ((Code str):rest) = (Str str):(deVerb rest)
|
deVerb ((Code str):rest) =
|
||||||
|
(Str $ "\\texttt{" ++ stringToLaTeX str ++ "}"):(deVerb rest)
|
||||||
deVerb (other:rest) = other:(deVerb rest)
|
deVerb (other:rest) = other:(deVerb rest)
|
||||||
|
|
||||||
-- | Convert Pandoc block element to LaTeX.
|
-- | Convert Pandoc block element to LaTeX.
|
||||||
blockToLaTeX :: Block -- ^ Block to convert
|
blockToLaTeX :: Block -- ^ Block to convert
|
||||||
-> String
|
-> State WriterState String
|
||||||
blockToLaTeX Null = ""
|
blockToLaTeX Null = return ""
|
||||||
blockToLaTeX (Plain lst) = inlineListToLaTeX lst ++ "\n"
|
blockToLaTeX (Plain lst) = (inlineListToLaTeX lst) >>= (return . (++ "\n"))
|
||||||
blockToLaTeX (Para lst) = (inlineListToLaTeX lst) ++ "\n\n"
|
blockToLaTeX (Para lst) = (inlineListToLaTeX lst) >>= (return . (++ "\n\n"))
|
||||||
blockToLaTeX (BlockQuote lst) = "\\begin{quote}\n" ++
|
blockToLaTeX (BlockQuote lst) = do
|
||||||
(concatMap blockToLaTeX lst) ++ "\\end{quote}\n"
|
contents <- blockListToLaTeX lst
|
||||||
blockToLaTeX (CodeBlock str) = "\\begin{verbatim}\n" ++ str ++
|
return $ "\\begin{quote}\n" ++ contents ++ "\\end{quote}\n"
|
||||||
"\n\\end{verbatim}\n"
|
blockToLaTeX (CodeBlock str) = return $
|
||||||
blockToLaTeX (RawHtml str) = ""
|
"\\begin{verbatim}\n" ++ str ++ "\n\\end{verbatim}\n"
|
||||||
blockToLaTeX (BulletList lst) = "\\begin{itemize}\n" ++
|
blockToLaTeX (RawHtml str) = return ""
|
||||||
(concatMap listItemToLaTeX lst) ++ "\\end{itemize}\n"
|
blockToLaTeX (BulletList lst) = do
|
||||||
blockToLaTeX (OrderedList lst) = "\\begin{enumerate}\n" ++
|
items <- mapM listItemToLaTeX lst
|
||||||
(concatMap listItemToLaTeX lst) ++ "\\end{enumerate}\n"
|
return $ "\\begin{itemize}\n" ++ concat items ++ "\\end{itemize}\n"
|
||||||
blockToLaTeX (DefinitionList lst) =
|
blockToLaTeX (OrderedList lst) = do
|
||||||
let defListItemToLaTeX (term, def) = "\\item[" ++
|
items <- mapM listItemToLaTeX lst
|
||||||
substitute "]" "\\]" (inlineListToLaTeX term) ++ "] " ++
|
return $ "\\begin{enumerate}\n" ++ concat items ++ "\\end{enumerate}\n"
|
||||||
concatMap blockToLaTeX def
|
blockToLaTeX (DefinitionList lst) = do
|
||||||
in "\\begin{description}\n" ++ concatMap defListItemToLaTeX lst ++
|
items <- mapM defListItemToLaTeX lst
|
||||||
"\\end{description}\n"
|
return $ "\\begin{description}\n" ++ concat items ++ "\\end{description}\n"
|
||||||
blockToLaTeX HorizontalRule =
|
blockToLaTeX HorizontalRule = return $
|
||||||
"\\begin{center}\\rule{3in}{0.4pt}\\end{center}\n\n"
|
"\\begin{center}\\rule{3in}{0.4pt}\\end{center}\n\n"
|
||||||
blockToLaTeX (Header level lst) =
|
blockToLaTeX (Header level lst) = do
|
||||||
if (level > 0) && (level <= 3)
|
text <- inlineListToLaTeX (deVerb lst)
|
||||||
then "\\" ++ (concat (replicate (level - 1) "sub")) ++ "section{" ++
|
return $ if (level > 0) && (level <= 3)
|
||||||
(inlineListToLaTeX (deVerb lst)) ++ "}\n\n"
|
then "\\" ++ (concat (replicate (level - 1) "sub")) ++
|
||||||
else (inlineListToLaTeX lst) ++ "\n\n"
|
"section{" ++ text ++ "}\n\n"
|
||||||
blockToLaTeX (Table caption aligns widths heads rows) =
|
else text ++ "\n\n"
|
||||||
let colWidths = map printDecimal widths
|
blockToLaTeX (Table caption aligns widths heads rows) = do
|
||||||
colDescriptors = concat $ zipWith
|
headers <- tableRowToLaTeX heads
|
||||||
(\width align -> ">{\\PBS" ++
|
captionText <- inlineListToLaTeX caption
|
||||||
(case align of
|
rows' <- mapM tableRowToLaTeX rows
|
||||||
AlignLeft -> "\\raggedright"
|
let colWidths = map (printf "%.2f") widths
|
||||||
AlignRight -> "\\raggedleft"
|
let colDescriptors = concat $ zipWith
|
||||||
AlignCenter -> "\\centering"
|
(\width align -> ">{\\PBS" ++
|
||||||
AlignDefault -> "\\raggedright") ++
|
(case align of
|
||||||
"\\hspace{0pt}}p{" ++ width ++
|
AlignLeft -> "\\raggedright"
|
||||||
"\\textwidth}")
|
AlignRight -> "\\raggedleft"
|
||||||
colWidths aligns
|
AlignCenter -> "\\centering"
|
||||||
headers = tableRowToLaTeX heads
|
AlignDefault -> "\\raggedright") ++
|
||||||
captionText = inlineListToLaTeX caption
|
"\\hspace{0pt}}p{" ++ width ++
|
||||||
tableBody = "\\begin{tabular}{" ++ colDescriptors ++ "}\n" ++
|
"\\textwidth}")
|
||||||
headers ++ "\\hline\n" ++
|
colWidths aligns
|
||||||
(concatMap tableRowToLaTeX rows) ++
|
let tableBody = "\\begin{tabular}{" ++ colDescriptors ++ "}\n" ++
|
||||||
"\\end{tabular}\n"
|
headers ++ "\\hline\n" ++ concat rows' ++ "\\end{tabular}\n"
|
||||||
centered str = "\\begin{center}\n" ++ str ++ "\\end{center}\n" in
|
let centered str = "\\begin{center}\n" ++ str ++ "\\end{center}\n"
|
||||||
if null captionText
|
addToHeader "\\usepackage{array}\n\
|
||||||
then centered tableBody ++ "\n"
|
\% This is needed because raggedright in table elements redefines //:\n\
|
||||||
else "\\begin{table}[h]\n" ++ centered tableBody ++ "\\caption{" ++
|
\\\newcommand{\\PreserveBackslash}[1]{\\let\\temp=\\\\#1\\let\\\\=\\temp}\n\
|
||||||
captionText ++ "}\n" ++ "\\end{table}\n\n"
|
\\\let\\PBS=\\PreserveBackslash"
|
||||||
|
return $ if null captionText
|
||||||
|
then centered tableBody ++ "\n"
|
||||||
|
else "\\begin{table}[h]\n" ++ centered tableBody ++ "\\caption{" ++
|
||||||
|
captionText ++ "}\n" ++ "\\end{table}\n\n"
|
||||||
|
|
||||||
printDecimal :: Float -> String
|
blockListToLaTeX lst = mapM blockToLaTeX lst >>= (return . concat)
|
||||||
printDecimal = printf "%.2f"
|
|
||||||
|
|
||||||
tableRowToLaTeX cols = joinWithSep " & " (map (concatMap blockToLaTeX) cols) ++ "\\\\\n"
|
tableRowToLaTeX cols =
|
||||||
|
mapM blockListToLaTeX cols >>= (return . (++ "\\\\\n") . (joinWithSep " & "))
|
||||||
|
|
||||||
listItemToLaTeX list = "\\item " ++
|
listItemToLaTeX lst = blockListToLaTeX lst >>= (return . ("\\item "++))
|
||||||
(concatMap blockToLaTeX list)
|
|
||||||
|
defListItemToLaTeX (term, def) = do
|
||||||
|
term' <- inlineListToLaTeX term
|
||||||
|
def' <- blockListToLaTeX def
|
||||||
|
return $ "\\item[" ++ substitute "]" "\\]" term' ++ "] " ++ def'
|
||||||
|
|
||||||
-- | Convert list of inline elements to LaTeX.
|
-- | Convert list of inline elements to LaTeX.
|
||||||
inlineListToLaTeX :: [Inline] -- ^ Inlines to convert
|
inlineListToLaTeX :: [Inline] -- ^ Inlines to convert
|
||||||
-> String
|
-> State WriterState String
|
||||||
inlineListToLaTeX lst =
|
inlineListToLaTeX lst =
|
||||||
concatMap inlineToLaTeX lst
|
mapM inlineToLaTeX lst >>= (return . concat)
|
||||||
|
|
||||||
isQuoted :: Inline -> Bool
|
isQuoted :: Inline -> Bool
|
||||||
isQuoted (Quoted _ _) = True
|
isQuoted (Quoted _ _) = True
|
||||||
|
@ -179,34 +200,58 @@ isQuoted _ = False
|
||||||
|
|
||||||
-- | Convert inline element to LaTeX
|
-- | Convert inline element to LaTeX
|
||||||
inlineToLaTeX :: Inline -- ^ Inline to convert
|
inlineToLaTeX :: Inline -- ^ Inline to convert
|
||||||
-> String
|
-> State WriterState String
|
||||||
inlineToLaTeX (Emph lst) = "\\emph{" ++
|
inlineToLaTeX (Emph lst) = do
|
||||||
(inlineListToLaTeX (deVerb lst)) ++ "}"
|
contents <- inlineListToLaTeX (deVerb lst)
|
||||||
inlineToLaTeX (Strong lst) = "\\textbf{" ++
|
return $ "\\emph{" ++ contents ++ "}"
|
||||||
(inlineListToLaTeX (deVerb lst)) ++ "}"
|
inlineToLaTeX (Strong lst) = do
|
||||||
inlineToLaTeX (Code str) = "\\verb" ++ [chr] ++ stuffing ++ [chr]
|
contents <- inlineListToLaTeX (deVerb lst)
|
||||||
|
return $ "\\textbf{" ++ contents ++ "}"
|
||||||
|
inlineToLaTeX (Strikeout lst) = do
|
||||||
|
contents <- inlineListToLaTeX (deVerb lst)
|
||||||
|
addToHeader "\\usepackage[normalem]{ulem}"
|
||||||
|
return $ "\\sout{" ++ contents ++ "}"
|
||||||
|
inlineToLaTeX (Superscript lst) = do
|
||||||
|
contents <- inlineListToLaTeX (deVerb lst)
|
||||||
|
return $ "\\textsuperscript{" ++ contents ++ "}"
|
||||||
|
inlineToLaTeX (Subscript lst) = do
|
||||||
|
contents <- inlineListToLaTeX (deVerb lst)
|
||||||
|
-- oddly, latex includes \textsuperscript but not \textsubscript
|
||||||
|
-- so we have to define it:
|
||||||
|
addToHeader "\\newcommand{\\textsubscript}[1]{\\ensuremath{_{\\scriptsize\\textrm{#1}}}}"
|
||||||
|
return $ "\\textsubscript{" ++ contents ++ "}"
|
||||||
|
inlineToLaTeX (Code str) = return $ "\\verb" ++ [chr] ++ stuffing ++ [chr]
|
||||||
where stuffing = str
|
where stuffing = str
|
||||||
chr = ((enumFromTo '!' '~') \\ stuffing) !! 0
|
chr = ((enumFromTo '!' '~') \\ stuffing) !! 0
|
||||||
inlineToLaTeX (Quoted SingleQuote lst) =
|
inlineToLaTeX (Quoted SingleQuote lst) = do
|
||||||
|
contents <- inlineListToLaTeX lst
|
||||||
let s1 = if (not (null lst)) && (isQuoted (head lst)) then "\\," else ""
|
let s1 = if (not (null lst)) && (isQuoted (head lst)) then "\\," else ""
|
||||||
s2 = if (not (null lst)) && (isQuoted (last lst)) then "\\," else "" in
|
let s2 = if (not (null lst)) && (isQuoted (last lst)) then "\\," else ""
|
||||||
"`" ++ s1 ++ inlineListToLaTeX lst ++ s2 ++ "'"
|
return $ "`" ++ s1 ++ contents ++ s2 ++ "'"
|
||||||
inlineToLaTeX (Quoted DoubleQuote lst) =
|
inlineToLaTeX (Quoted DoubleQuote lst) = do
|
||||||
|
contents <- inlineListToLaTeX lst
|
||||||
let s1 = if (not (null lst)) && (isQuoted (head lst)) then "\\," else ""
|
let s1 = if (not (null lst)) && (isQuoted (head lst)) then "\\," else ""
|
||||||
s2 = if (not (null lst)) && (isQuoted (last lst)) then "\\," else "" in
|
let s2 = if (not (null lst)) && (isQuoted (last lst)) then "\\," else ""
|
||||||
"``" ++ s1 ++ inlineListToLaTeX lst ++ s2 ++ "''"
|
return $ "``" ++ s1 ++ contents ++ s2 ++ "''"
|
||||||
inlineToLaTeX Apostrophe = "'"
|
inlineToLaTeX Apostrophe = return "'"
|
||||||
inlineToLaTeX EmDash = "---"
|
inlineToLaTeX EmDash = return "---"
|
||||||
inlineToLaTeX EnDash = "--"
|
inlineToLaTeX EnDash = return "--"
|
||||||
inlineToLaTeX Ellipses = "\\ldots{}"
|
inlineToLaTeX Ellipses = return "\\ldots{}"
|
||||||
inlineToLaTeX (Str str) = stringToLaTeX str
|
inlineToLaTeX (Str str) = return $ stringToLaTeX str
|
||||||
inlineToLaTeX (TeX str) = str
|
inlineToLaTeX (TeX str) = return str
|
||||||
inlineToLaTeX (HtmlInline str) = ""
|
inlineToLaTeX (HtmlInline str) = return ""
|
||||||
inlineToLaTeX (LineBreak) = "\\\\\n"
|
inlineToLaTeX (LineBreak) = return "\\\\\n"
|
||||||
inlineToLaTeX Space = " "
|
inlineToLaTeX Space = return " "
|
||||||
inlineToLaTeX (Link text (src, tit)) =
|
inlineToLaTeX (Link text (src, tit)) = do
|
||||||
"\\href{" ++ src ++ "}{" ++ (inlineListToLaTeX (deVerb text)) ++ "}"
|
contents <- inlineListToLaTeX (deVerb text)
|
||||||
inlineToLaTeX (Image alternate (source, tit)) =
|
addToHeader "\\usepackage[breaklinks=true]{hyperref}"
|
||||||
"\\includegraphics{" ++ source ++ "}"
|
return $ "\\href{" ++ src ++ "}{" ++ contents ++ "}"
|
||||||
inlineToLaTeX (Note contents) =
|
inlineToLaTeX (Image alternate (source, tit)) = do
|
||||||
"\\footnote{" ++ (stripTrailingNewlines $ concatMap blockToLaTeX contents) ++ "}"
|
addToHeader "\\usepackage{graphicx}"
|
||||||
|
return $ "\\includegraphics{" ++ source ++ "}"
|
||||||
|
inlineToLaTeX (Note contents) = do
|
||||||
|
addToHeader "% This is needed for code blocks in footnotes:\n\
|
||||||
|
\\\usepackage{fancyvrb}\n\\VerbatimFootnotes"
|
||||||
|
contents' <- blockListToLaTeX contents
|
||||||
|
return $ "\\footnote{" ++ stripTrailingNewlines contents' ++ "}"
|
||||||
|
|
||||||
|
|
|
@ -108,27 +108,18 @@ wrappedMan opts sect = do
|
||||||
chunks' <- mapM (inlineListToMan opts) chunks
|
chunks' <- mapM (inlineListToMan opts) chunks
|
||||||
return $ fsep chunks'
|
return $ fsep chunks'
|
||||||
|
|
||||||
-- | Escape nonbreaking space as \
|
-- | Association list of characters to escape.
|
||||||
escapeNbsp "" = ""
|
manEscapes :: [(Char, String)]
|
||||||
escapeNbsp ('\160':xs) = "\\ " ++ escapeNbsp xs
|
manEscapes = [('\160', "\\ "), ('\'', "\\[aq]")] ++
|
||||||
escapeNbsp str =
|
backslashEscapes "\".@\\"
|
||||||
let (a,b) = break (=='\160') str in
|
|
||||||
a ++ escapeNbsp b
|
|
||||||
|
|
||||||
-- | Escape single quote as \[aq]
|
|
||||||
escapeSingleQuote "" = ""
|
|
||||||
escapeSingleQuote ('\'':xs) = "\\[aq]" ++ escapeSingleQuote xs
|
|
||||||
escapeSingleQuote str =
|
|
||||||
let (a,b) = break (=='\160') str in
|
|
||||||
a ++ escapeSingleQuote b
|
|
||||||
|
|
||||||
-- | Escape special characters for Man.
|
-- | Escape special characters for Man.
|
||||||
escapeString :: String -> String
|
escapeString :: String -> String
|
||||||
escapeString = escapeSingleQuote . escapeNbsp . backslashEscape "\".@\\"
|
escapeString = escapeStringUsing manEscapes
|
||||||
|
|
||||||
-- | Escape a literal (code) section for Man.
|
-- | Escape a literal (code) section for Man.
|
||||||
escapeCode :: String -> String
|
escapeCode :: String -> String
|
||||||
escapeCode = backslashEscape "\t " . escapeString
|
escapeCode = escapeStringUsing (manEscapes ++ backslashEscapes "\t ")
|
||||||
|
|
||||||
-- | Convert Pandoc block element to man.
|
-- | Convert Pandoc block element to man.
|
||||||
blockToMan :: WriterOptions -- ^ Options
|
blockToMan :: WriterOptions -- ^ Options
|
||||||
|
@ -267,6 +258,12 @@ inlineToMan opts (Emph lst) = do
|
||||||
inlineToMan opts (Strong lst) = do
|
inlineToMan opts (Strong lst) = do
|
||||||
contents <- inlineListToMan opts lst
|
contents <- inlineListToMan opts lst
|
||||||
return $ text "\\f[B]" <> contents <> text "\\f[]"
|
return $ text "\\f[B]" <> contents <> text "\\f[]"
|
||||||
|
inlineToMan opts (Strikeout lst) = do
|
||||||
|
contents <- inlineListToMan opts lst
|
||||||
|
return $ text "[STRIKEOUT:" <> contents <> text "]"
|
||||||
|
-- just treat superscripts and subscripts like normal text
|
||||||
|
inlineToMan opts (Superscript lst) = inlineListToMan opts lst
|
||||||
|
inlineToMan opts (Subscript lst) = inlineListToMan opts lst
|
||||||
inlineToMan opts (Quoted SingleQuote lst) = do
|
inlineToMan opts (Quoted SingleQuote lst) = do
|
||||||
contents <- inlineListToMan opts lst
|
contents <- inlineListToMan opts lst
|
||||||
return $ char '`' <> contents <> char '\''
|
return $ char '`' <> contents <> char '\''
|
||||||
|
|
|
@ -276,12 +276,20 @@ inlineToMarkdown :: WriterOptions -> Inline -> State WriterState Doc
|
||||||
inlineToMarkdown opts (Emph lst) = do
|
inlineToMarkdown opts (Emph lst) = do
|
||||||
contents <- inlineListToMarkdown opts lst
|
contents <- inlineListToMarkdown opts lst
|
||||||
return $ text "*" <> contents <> text "*"
|
return $ text "*" <> contents <> text "*"
|
||||||
inlineToMarkdown opts (Strikeout lst) = do
|
|
||||||
contents <- inlineListToMarkdown opts lst
|
|
||||||
return $ text "~" <> contents <> text "~"
|
|
||||||
inlineToMarkdown opts (Strong lst) = do
|
inlineToMarkdown opts (Strong lst) = do
|
||||||
contents <- inlineListToMarkdown opts lst
|
contents <- inlineListToMarkdown opts lst
|
||||||
return $ text "**" <> contents <> text "**"
|
return $ text "**" <> contents <> text "**"
|
||||||
|
inlineToMarkdown opts (Strikeout lst) = do
|
||||||
|
contents <- inlineListToMarkdown opts lst
|
||||||
|
return $ text "~~" <> contents <> text "~~"
|
||||||
|
inlineToMarkdown opts (Superscript lst) = do
|
||||||
|
contents <- inlineListToMarkdown opts lst
|
||||||
|
let contents' = text $ substitute " " "\\ " $ render contents
|
||||||
|
return $ text "^" <> contents' <> text "^"
|
||||||
|
inlineToMarkdown opts (Subscript lst) = do
|
||||||
|
contents <- inlineListToMarkdown opts lst
|
||||||
|
let contents' = text $ substitute " " "\\ " $ render contents
|
||||||
|
return $ text "~" <> contents' <> text "~"
|
||||||
inlineToMarkdown opts (Quoted SingleQuote lst) = do
|
inlineToMarkdown opts (Quoted SingleQuote lst) = do
|
||||||
contents <- inlineListToMarkdown opts lst
|
contents <- inlineListToMarkdown opts lst
|
||||||
return $ char '\'' <> contents <> char '\''
|
return $ char '\'' <> contents <> char '\''
|
||||||
|
|
|
@ -122,7 +122,7 @@ wrappedRSTSection opts sect = do
|
||||||
|
|
||||||
-- | Escape special characters for RST.
|
-- | Escape special characters for RST.
|
||||||
escapeString :: String -> String
|
escapeString :: String -> String
|
||||||
escapeString = backslashEscape "`\\|*_"
|
escapeString = escapeStringUsing (backslashEscapes "`\\|*_")
|
||||||
|
|
||||||
-- | Convert bibliographic information into RST header.
|
-- | Convert bibliographic information into RST header.
|
||||||
metaToRST :: WriterOptions -> Meta -> State WriterState Doc
|
metaToRST :: WriterOptions -> Meta -> State WriterState Doc
|
||||||
|
@ -266,6 +266,15 @@ inlineToRST opts (Emph lst) = do
|
||||||
inlineToRST opts (Strong lst) = do
|
inlineToRST opts (Strong lst) = do
|
||||||
contents <- inlineListToRST opts lst
|
contents <- inlineListToRST opts lst
|
||||||
return $ text "**" <> contents <> text "**"
|
return $ text "**" <> contents <> text "**"
|
||||||
|
inlineToRST opts (Strikeout lst) = do
|
||||||
|
contents <- inlineListToRST opts lst
|
||||||
|
return $ text "[STRIKEOUT:" <> contents <> text "]"
|
||||||
|
inlineToRST opts (Superscript lst) = do
|
||||||
|
contents <- inlineListToRST opts lst
|
||||||
|
return $ text "\\ :sup:`" <> contents <> text "`\\ "
|
||||||
|
inlineToRST opts (Subscript lst) = do
|
||||||
|
contents <- inlineListToRST opts lst
|
||||||
|
return $ text "\\ :sub:`" <> contents <> text "`\\ "
|
||||||
inlineToRST opts (Quoted SingleQuote lst) = do
|
inlineToRST opts (Quoted SingleQuote lst) = do
|
||||||
contents <- inlineListToRST opts lst
|
contents <- inlineListToRST opts lst
|
||||||
return $ char '\'' <> contents <> char '\''
|
return $ char '\'' <> contents <> char '\''
|
||||||
|
|
|
@ -72,25 +72,21 @@ handleUnicode (c:cs) = if (ord c) > 127
|
||||||
(handleUnicode cs)
|
(handleUnicode cs)
|
||||||
else c:(handleUnicode cs)
|
else c:(handleUnicode cs)
|
||||||
|
|
||||||
escapeSpecial = backslashEscape "{\\}"
|
-- | Escape special characters.
|
||||||
escapeTab = substitute "\\t" "\\tab "
|
escapeSpecial :: String -> String
|
||||||
|
escapeSpecial = escapeStringUsing (('\t',"\\tab "):(backslashEscapes "{\\}"))
|
||||||
|
|
||||||
-- | Escape strings as needed for rich text format.
|
-- | Escape strings as needed for rich text format.
|
||||||
stringToRTF :: String -> String
|
stringToRTF :: String -> String
|
||||||
stringToRTF = handleUnicode . escapeSpecial . escapeTab
|
stringToRTF = handleUnicode . escapeSpecial
|
||||||
|
|
||||||
-- | Escape raw LaTeX strings for RTF. Don't escape \t; it might
|
|
||||||
-- be the first letter of a command!
|
|
||||||
latexStringToRTF :: String -> String
|
|
||||||
latexStringToRTF = handleUnicode . escapeSpecial
|
|
||||||
|
|
||||||
-- | Escape things as needed for code block in RTF.
|
-- | Escape things as needed for code block in RTF.
|
||||||
codeStringToRTF :: String -> String
|
codeStringToRTF :: String -> String
|
||||||
codeStringToRTF str = joinWithSep "\\line\n" (lines (stringToRTF str))
|
codeStringToRTF str = joinWithSep "\\line\n" $ lines (stringToRTF str)
|
||||||
|
|
||||||
-- | Deal with raw LaTeX.
|
-- | Deal with raw LaTeX.
|
||||||
latexToRTF :: String -> String
|
latexToRTF :: String -> String
|
||||||
latexToRTF str = "{\\cf1 " ++ (latexStringToRTF str) ++ "\\cf0 } "
|
latexToRTF str = "{\\cf1 " ++ (stringToRTF str) ++ "\\cf0 } "
|
||||||
|
|
||||||
-- | Make a paragraph with first-line indent, block indent, and space after.
|
-- | Make a paragraph with first-line indent, block indent, and space after.
|
||||||
rtfParSpaced :: Int -- ^ space after (in twips)
|
rtfParSpaced :: Int -- ^ space after (in twips)
|
||||||
|
@ -261,8 +257,10 @@ inlineListToRTF lst = concatMap inlineToRTF lst
|
||||||
inlineToRTF :: Inline -- ^ inline to convert
|
inlineToRTF :: Inline -- ^ inline to convert
|
||||||
-> String
|
-> String
|
||||||
inlineToRTF (Emph lst) = "{\\i " ++ (inlineListToRTF lst) ++ "} "
|
inlineToRTF (Emph lst) = "{\\i " ++ (inlineListToRTF lst) ++ "} "
|
||||||
inlineToRTF (Strong lst) =
|
inlineToRTF (Strong lst) = "{\\b " ++ (inlineListToRTF lst) ++ "} "
|
||||||
"{\\b " ++ (inlineListToRTF lst) ++ "} "
|
inlineToRTF (Strikeout lst) = "{\\strike " ++ (inlineListToRTF lst) ++ "} "
|
||||||
|
inlineToRTF (Superscript lst) = "{\\super " ++ (inlineListToRTF lst) ++ "} "
|
||||||
|
inlineToRTF (Subscript lst) = "{\\sub " ++ (inlineListToRTF lst) ++ "} "
|
||||||
inlineToRTF (Quoted SingleQuote lst) =
|
inlineToRTF (Quoted SingleQuote lst) =
|
||||||
"\\u8216'" ++ (inlineListToRTF lst) ++ "\\u8217'"
|
"\\u8216'" ++ (inlineListToRTF lst) ++ "\\u8217'"
|
||||||
inlineToRTF (Quoted DoubleQuote lst) =
|
inlineToRTF (Quoted DoubleQuote lst) =
|
||||||
|
|
Loading…
Add table
Reference in a new issue