aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Writers/ConTeXt.hs11
-rw-r--r--src/Text/Pandoc/Writers/Docbook.hs7
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs43
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs309
-rw-r--r--src/Text/Pandoc/Writers/Man.hs27
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs14
-rw-r--r--src/Text/Pandoc/Writers/RST.hs11
-rw-r--r--src/Text/Pandoc/Writers/RTF.hs22
8 files changed, 263 insertions, 181 deletions
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index 8e35ea9d5..2cf2b136b 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -192,6 +192,15 @@ inlineToConTeXt (Emph lst) = do
inlineToConTeXt (Strong lst) = do
contents <- inlineListToConTeXt lst
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 (Quoted SingleQuote lst) = do
contents <- inlineListToConTeXt lst
@@ -206,7 +215,7 @@ inlineToConTeXt Ellipses = return "\\ldots{}"
inlineToConTeXt (Str str) = return $ stringToConTeXt str
inlineToConTeXt (TeX str) = return str
inlineToConTeXt (HtmlInline str) = return ""
-inlineToConTeXt (LineBreak) = return "\\hfil\\break\n"
+inlineToConTeXt (LineBreak) = return "\\crlf\n"
inlineToConTeXt Space = return " "
inlineToConTeXt (Link text (src, _)) = do
next <- get
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs
index 7366ee59c..2bb29da6c 100644
--- a/src/Text/Pandoc/Writers/Docbook.hs
+++ b/src/Text/Pandoc/Writers/Docbook.hs
@@ -233,6 +233,13 @@ inlineToDocbook opts (Emph lst) =
inlineToDocbook opts (Strong lst) =
inTags False "emphasis" [("role", "strong")]
(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) =
inTagsSimple "quote" (inlinesToDocbook opts lst)
inlineToDocbook opts Apostrophe = text "'"
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index ad31969ed..d8fbdb9b4 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -66,6 +66,7 @@ writeHtml opts (Pandoc (Meta tit authors date) blocks) =
(if null date
then noHtml
else meta ! [name "date", content date]) +++
+ (style ! [thetype "text/css"] $ (stringToHtml ".strikeout { text-decoration: line-through; }")) +++
primHtml (writerHeader opts)
titleHeader = if (writerStandalone opts) && (not (null tit)) &&
(not (writerS5 opts))
@@ -179,23 +180,27 @@ inlineListToIdentifier [] = ""
inlineListToIdentifier (x:xs) =
xAsText ++ inlineListToIdentifier xs
where xAsText = case x of
- Str s -> filter (\c -> (c == '-') || not (isPunctuation c)) $
- concat $ intersperse "-" $ words $ map toLower s
- Emph lst -> inlineListToIdentifier lst
- Strong lst -> inlineListToIdentifier lst
- Quoted _ lst -> inlineListToIdentifier lst
- Code s -> s
- Space -> "-"
- EmDash -> "-"
- EnDash -> "-"
- Apostrophe -> ""
- Ellipses -> ""
- LineBreak -> "-"
- TeX _ -> ""
- HtmlInline _ -> ""
- Link lst _ -> inlineListToIdentifier lst
- Image lst _ -> inlineListToIdentifier lst
- Note _ -> ""
+ Str s -> filter
+ (\c -> (c == '-') || not (isPunctuation c)) $
+ concat $ intersperse "-" $ words $ map toLower s
+ Emph lst -> inlineListToIdentifier lst
+ Strikeout lst -> inlineListToIdentifier lst
+ Superscript lst -> inlineListToIdentifier lst
+ Subscript lst -> inlineListToIdentifier lst
+ Strong lst -> inlineListToIdentifier lst
+ Quoted _ lst -> inlineListToIdentifier lst
+ Code s -> s
+ Space -> "-"
+ EmDash -> "-"
+ EnDash -> "-"
+ Apostrophe -> ""
+ Ellipses -> ""
+ LineBreak -> "-"
+ TeX _ -> ""
+ HtmlInline _ -> ""
+ Link lst _ -> inlineListToIdentifier lst
+ Image lst _ -> inlineListToIdentifier lst
+ Note _ -> ""
-- | Return unique identifiers for list of inline lists.
uniqueIdentifiers :: [[Inline]] -> [String]
@@ -326,6 +331,10 @@ inlineToHtml opts inline =
(Emph lst) -> inlineListToHtml opts lst >>= (return . emphasize)
(Strong lst) -> inlineListToHtml opts lst >>= (return . strong)
(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) ->
let (leftQuote, rightQuote) = case quoteType of
SingleQuote -> (primHtmlChar "lsquo",
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index e0c80d24e..f0bb92002 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -34,143 +34,164 @@ import Text.Pandoc.Definition
import Text.Pandoc.Shared
import Text.Printf ( printf )
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.
writeLaTeX :: WriterOptions -> Pandoc -> String
-writeLaTeX options (Pandoc meta blocks) =
- let body = (writerIncludeBefore options) ++
- (concatMap blockToLaTeX blocks) ++
- (writerIncludeAfter options)
- head = if writerStandalone options
- then latexHeader options meta
- else ""
- toc = if writerTableOfContents options
- then "\\tableofcontents\n\n"
- else ""
- foot = if writerStandalone options
+writeLaTeX options document =
+ evalState (pandocToLaTeX options document) S.empty
+
+pandocToLaTeX :: WriterOptions -> Pandoc -> State WriterState String
+pandocToLaTeX options (Pandoc meta blocks) = do
+ main <- blockListToLaTeX blocks
+ head <- if writerStandalone options
+ then latexHeader options meta
+ else return ""
+ let body = writerIncludeBefore options ++ main ++
+ writerIncludeAfter options
+ let toc = if writerTableOfContents options
+ then "\\tableofcontents\n\n"
+ else ""
+ let foot = if writerStandalone options
then "\n\\end{document}\n"
else ""
- in head ++ toc ++ body ++ foot
+ return $ head ++ toc ++ body ++ foot
-- | Insert bibliographic information into LaTeX header.
latexHeader :: WriterOptions -- ^ Options, including LaTeX header
-> Meta -- ^ Meta with bibliographic information
- -> String
-latexHeader options (Meta title authors date) =
- let titletext = if null title
- then ""
- else "\\title{" ++ inlineListToLaTeX title ++ "}\n"
- authorstext = if null authors
+ -> State WriterState String
+latexHeader options (Meta title authors date) = do
+ titletext <- if null title
+ then return ""
+ else do title' <- inlineListToLaTeX title
+ return $ "\\title{" ++ title' ++ "}\n"
+ extras <- get
+ let authorstext = if null authors
then ""
else "\\author{" ++ (joinWithSep "\\\\"
(map stringToLaTeX authors)) ++ "}\n"
- datetext = if date == ""
- then ""
- else "\\date{" ++ stringToLaTeX date ++ "}\n"
- maketitle = if null title then "" else "\\maketitle\n\n"
- secnumline = if (writerNumberSections options)
+ let datetext = if date == ""
+ then ""
+ else "\\date{" ++ stringToLaTeX date ++ "}\n"
+ let maketitle = if null title then "" else "\\maketitle\n\n"
+ let secnumline = if (writerNumberSections options)
then ""
else "\\setcounter{secnumdepth}{0}\n"
- header = writerHeader options in
- header ++ secnumline ++ titletext ++ authorstext ++ datetext ++
- "\\begin{document}\n" ++ maketitle
+ let baseHeader = writerHeader options
+ let header = baseHeader ++ (unlines $ S.toList extras)
+ return $ header ++ secnumline ++ titletext ++ authorstext ++ datetext ++
+ "\\begin{document}\n" ++ maketitle
-- 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 = concatMap escapeCharForLaTeX
+stringToLaTeX = escapeStringUsing latexEscapes
+ where latexEscapes = [
+ ('\\', "\\textbackslash{}"),
+ ('{', "\\{"),
+ ('}', "\\}"),
+ ('$', "\\$"),
+ ('%', "\\%"),
+ ('&', "\\&"),
+ ('~', "\\~"),
+ ('_', "\\_"),
+ ('#', "\\#"),
+ ('^', "\\^{}"),
+ ('|', "\\textbar{}"),
+ ('<', "\\textless{}"),
+ ('>', "\\textgreater{}")
+ ]
-- | Remove all code elements from list of inline elements
-- (because it's illegal to have a \\verb inside a command argument)
deVerb :: [Inline] -> [Inline]
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)
-- | Convert Pandoc block element to LaTeX.
blockToLaTeX :: Block -- ^ Block to convert
- -> String
-blockToLaTeX Null = ""
-blockToLaTeX (Plain lst) = inlineListToLaTeX lst ++ "\n"
-blockToLaTeX (Para lst) = (inlineListToLaTeX lst) ++ "\n\n"
-blockToLaTeX (BlockQuote lst) = "\\begin{quote}\n" ++
- (concatMap blockToLaTeX lst) ++ "\\end{quote}\n"
-blockToLaTeX (CodeBlock str) = "\\begin{verbatim}\n" ++ str ++
- "\n\\end{verbatim}\n"
-blockToLaTeX (RawHtml str) = ""
-blockToLaTeX (BulletList lst) = "\\begin{itemize}\n" ++
- (concatMap listItemToLaTeX lst) ++ "\\end{itemize}\n"
-blockToLaTeX (OrderedList lst) = "\\begin{enumerate}\n" ++
- (concatMap listItemToLaTeX lst) ++ "\\end{enumerate}\n"
-blockToLaTeX (DefinitionList lst) =
- let defListItemToLaTeX (term, def) = "\\item[" ++
- substitute "]" "\\]" (inlineListToLaTeX term) ++ "] " ++
- concatMap blockToLaTeX def
- in "\\begin{description}\n" ++ concatMap defListItemToLaTeX lst ++
- "\\end{description}\n"
-blockToLaTeX HorizontalRule =
+ -> State WriterState String
+blockToLaTeX Null = return ""
+blockToLaTeX (Plain lst) = (inlineListToLaTeX lst) >>= (return . (++ "\n"))
+blockToLaTeX (Para lst) = (inlineListToLaTeX lst) >>= (return . (++ "\n\n"))
+blockToLaTeX (BlockQuote lst) = do
+ contents <- blockListToLaTeX lst
+ return $ "\\begin{quote}\n" ++ contents ++ "\\end{quote}\n"
+blockToLaTeX (CodeBlock str) = return $
+ "\\begin{verbatim}\n" ++ str ++ "\n\\end{verbatim}\n"
+blockToLaTeX (RawHtml str) = return ""
+blockToLaTeX (BulletList lst) = do
+ items <- mapM listItemToLaTeX lst
+ return $ "\\begin{itemize}\n" ++ concat items ++ "\\end{itemize}\n"
+blockToLaTeX (OrderedList lst) = do
+ items <- mapM listItemToLaTeX lst
+ return $ "\\begin{enumerate}\n" ++ concat items ++ "\\end{enumerate}\n"
+blockToLaTeX (DefinitionList lst) = do
+ items <- mapM defListItemToLaTeX lst
+ return $ "\\begin{description}\n" ++ concat items ++ "\\end{description}\n"
+blockToLaTeX HorizontalRule = return $
"\\begin{center}\\rule{3in}{0.4pt}\\end{center}\n\n"
-blockToLaTeX (Header level lst) =
- if (level > 0) && (level <= 3)
- then "\\" ++ (concat (replicate (level - 1) "sub")) ++ "section{" ++
- (inlineListToLaTeX (deVerb lst)) ++ "}\n\n"
- else (inlineListToLaTeX lst) ++ "\n\n"
-blockToLaTeX (Table caption aligns widths heads rows) =
- let colWidths = map printDecimal widths
- colDescriptors = concat $ zipWith
- (\width align -> ">{\\PBS" ++
- (case align of
- AlignLeft -> "\\raggedright"
- AlignRight -> "\\raggedleft"
- AlignCenter -> "\\centering"
- AlignDefault -> "\\raggedright") ++
- "\\hspace{0pt}}p{" ++ width ++
- "\\textwidth}")
- colWidths aligns
- headers = tableRowToLaTeX heads
- captionText = inlineListToLaTeX caption
- tableBody = "\\begin{tabular}{" ++ colDescriptors ++ "}\n" ++
- headers ++ "\\hline\n" ++
- (concatMap tableRowToLaTeX rows) ++
- "\\end{tabular}\n"
- centered str = "\\begin{center}\n" ++ str ++ "\\end{center}\n" in
- if null captionText
- then centered tableBody ++ "\n"
- else "\\begin{table}[h]\n" ++ centered tableBody ++ "\\caption{" ++
- captionText ++ "}\n" ++ "\\end{table}\n\n"
-
-printDecimal :: Float -> String
-printDecimal = printf "%.2f"
-
-tableRowToLaTeX cols = joinWithSep " & " (map (concatMap blockToLaTeX) cols) ++ "\\\\\n"
-
-listItemToLaTeX list = "\\item " ++
- (concatMap blockToLaTeX list)
+blockToLaTeX (Header level lst) = do
+ text <- inlineListToLaTeX (deVerb lst)
+ return $ if (level > 0) && (level <= 3)
+ then "\\" ++ (concat (replicate (level - 1) "sub")) ++
+ "section{" ++ text ++ "}\n\n"
+ else text ++ "\n\n"
+blockToLaTeX (Table caption aligns widths heads rows) = do
+ headers <- tableRowToLaTeX heads
+ captionText <- inlineListToLaTeX caption
+ rows' <- mapM tableRowToLaTeX rows
+ let colWidths = map (printf "%.2f") widths
+ let colDescriptors = concat $ zipWith
+ (\width align -> ">{\\PBS" ++
+ (case align of
+ AlignLeft -> "\\raggedright"
+ AlignRight -> "\\raggedleft"
+ AlignCenter -> "\\centering"
+ AlignDefault -> "\\raggedright") ++
+ "\\hspace{0pt}}p{" ++ width ++
+ "\\textwidth}")
+ colWidths aligns
+ let tableBody = "\\begin{tabular}{" ++ colDescriptors ++ "}\n" ++
+ headers ++ "\\hline\n" ++ concat rows' ++ "\\end{tabular}\n"
+ let centered str = "\\begin{center}\n" ++ str ++ "\\end{center}\n"
+ addToHeader "\\usepackage{array}\n\
+ \% This is needed because raggedright in table elements redefines //:\n\
+ \\\newcommand{\\PreserveBackslash}[1]{\\let\\temp=\\\\#1\\let\\\\=\\temp}\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"
+
+blockListToLaTeX lst = mapM blockToLaTeX lst >>= (return . concat)
+
+tableRowToLaTeX cols =
+ mapM blockListToLaTeX cols >>= (return . (++ "\\\\\n") . (joinWithSep " & "))
+
+listItemToLaTeX lst = blockListToLaTeX lst >>= (return . ("\\item "++))
+
+defListItemToLaTeX (term, def) = do
+ term' <- inlineListToLaTeX term
+ def' <- blockListToLaTeX def
+ return $ "\\item[" ++ substitute "]" "\\]" term' ++ "] " ++ def'
-- | Convert list of inline elements to LaTeX.
inlineListToLaTeX :: [Inline] -- ^ Inlines to convert
- -> String
+ -> State WriterState String
inlineListToLaTeX lst =
- concatMap inlineToLaTeX lst
+ mapM inlineToLaTeX lst >>= (return . concat)
isQuoted :: Inline -> Bool
isQuoted (Quoted _ _) = True
@@ -179,34 +200,58 @@ isQuoted _ = False
-- | Convert inline element to LaTeX
inlineToLaTeX :: Inline -- ^ Inline to convert
- -> String
-inlineToLaTeX (Emph lst) = "\\emph{" ++
- (inlineListToLaTeX (deVerb lst)) ++ "}"
-inlineToLaTeX (Strong lst) = "\\textbf{" ++
- (inlineListToLaTeX (deVerb lst)) ++ "}"
-inlineToLaTeX (Code str) = "\\verb" ++ [chr] ++ stuffing ++ [chr]
+ -> State WriterState String
+inlineToLaTeX (Emph lst) = do
+ contents <- inlineListToLaTeX (deVerb lst)
+ return $ "\\emph{" ++ contents ++ "}"
+inlineToLaTeX (Strong lst) = do
+ 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
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 ""
- s2 = if (not (null lst)) && (isQuoted (last lst)) then "\\," else "" in
- "`" ++ s1 ++ inlineListToLaTeX lst ++ s2 ++ "'"
-inlineToLaTeX (Quoted DoubleQuote lst) =
+ let s2 = if (not (null lst)) && (isQuoted (last lst)) then "\\," else ""
+ return $ "`" ++ s1 ++ contents ++ s2 ++ "'"
+inlineToLaTeX (Quoted DoubleQuote lst) = do
+ contents <- inlineListToLaTeX lst
let s1 = if (not (null lst)) && (isQuoted (head lst)) then "\\," else ""
- s2 = if (not (null lst)) && (isQuoted (last lst)) then "\\," else "" in
- "``" ++ s1 ++ inlineListToLaTeX lst ++ s2 ++ "''"
-inlineToLaTeX Apostrophe = "'"
-inlineToLaTeX EmDash = "---"
-inlineToLaTeX EnDash = "--"
-inlineToLaTeX Ellipses = "\\ldots{}"
-inlineToLaTeX (Str str) = stringToLaTeX str
-inlineToLaTeX (TeX str) = str
-inlineToLaTeX (HtmlInline str) = ""
-inlineToLaTeX (LineBreak) = "\\\\\n"
-inlineToLaTeX Space = " "
-inlineToLaTeX (Link text (src, tit)) =
- "\\href{" ++ src ++ "}{" ++ (inlineListToLaTeX (deVerb text)) ++ "}"
-inlineToLaTeX (Image alternate (source, tit)) =
- "\\includegraphics{" ++ source ++ "}"
-inlineToLaTeX (Note contents) =
- "\\footnote{" ++ (stripTrailingNewlines $ concatMap blockToLaTeX contents) ++ "}"
+ let s2 = if (not (null lst)) && (isQuoted (last lst)) then "\\," else ""
+ return $ "``" ++ s1 ++ contents ++ s2 ++ "''"
+inlineToLaTeX Apostrophe = return "'"
+inlineToLaTeX EmDash = return "---"
+inlineToLaTeX EnDash = return "--"
+inlineToLaTeX Ellipses = return "\\ldots{}"
+inlineToLaTeX (Str str) = return $ stringToLaTeX str
+inlineToLaTeX (TeX str) = return str
+inlineToLaTeX (HtmlInline str) = return ""
+inlineToLaTeX (LineBreak) = return "\\\\\n"
+inlineToLaTeX Space = return " "
+inlineToLaTeX (Link text (src, tit)) = do
+ contents <- inlineListToLaTeX (deVerb text)
+ addToHeader "\\usepackage[breaklinks=true]{hyperref}"
+ return $ "\\href{" ++ src ++ "}{" ++ contents ++ "}"
+inlineToLaTeX (Image alternate (source, tit)) = do
+ 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' ++ "}"
+
diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs
index 318fb056a..67d37288e 100644
--- a/src/Text/Pandoc/Writers/Man.hs
+++ b/src/Text/Pandoc/Writers/Man.hs
@@ -108,27 +108,18 @@ wrappedMan opts sect = do
chunks' <- mapM (inlineListToMan opts) chunks
return $ fsep chunks'
--- | Escape nonbreaking space as \
-escapeNbsp "" = ""
-escapeNbsp ('\160':xs) = "\\ " ++ escapeNbsp xs
-escapeNbsp str =
- 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
+-- | Association list of characters to escape.
+manEscapes :: [(Char, String)]
+manEscapes = [('\160', "\\ "), ('\'', "\\[aq]")] ++
+ backslashEscapes "\".@\\"
-- | Escape special characters for Man.
escapeString :: String -> String
-escapeString = escapeSingleQuote . escapeNbsp . backslashEscape "\".@\\"
+escapeString = escapeStringUsing manEscapes
-- | Escape a literal (code) section for Man.
escapeCode :: String -> String
-escapeCode = backslashEscape "\t " . escapeString
+escapeCode = escapeStringUsing (manEscapes ++ backslashEscapes "\t ")
-- | Convert Pandoc block element to man.
blockToMan :: WriterOptions -- ^ Options
@@ -267,6 +258,12 @@ inlineToMan opts (Emph lst) = do
inlineToMan opts (Strong lst) = do
contents <- inlineListToMan opts lst
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
contents <- inlineListToMan opts lst
return $ char '`' <> contents <> char '\''
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index 1af9b9625..b55885509 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -276,12 +276,20 @@ inlineToMarkdown :: WriterOptions -> Inline -> State WriterState Doc
inlineToMarkdown opts (Emph lst) = do
contents <- inlineListToMarkdown opts lst
return $ text "*" <> contents <> text "*"
-inlineToMarkdown opts (Strikeout lst) = do
- contents <- inlineListToMarkdown opts lst
- return $ text "~" <> contents <> text "~"
inlineToMarkdown opts (Strong lst) = do
contents <- inlineListToMarkdown opts lst
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
contents <- inlineListToMarkdown opts lst
return $ char '\'' <> contents <> char '\''
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index b79ce1d94..479d40b00 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -122,7 +122,7 @@ wrappedRSTSection opts sect = do
-- | Escape special characters for RST.
escapeString :: String -> String
-escapeString = backslashEscape "`\\|*_"
+escapeString = escapeStringUsing (backslashEscapes "`\\|*_")
-- | Convert bibliographic information into RST header.
metaToRST :: WriterOptions -> Meta -> State WriterState Doc
@@ -266,6 +266,15 @@ inlineToRST opts (Emph lst) = do
inlineToRST opts (Strong lst) = do
contents <- inlineListToRST opts lst
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
contents <- inlineListToRST opts lst
return $ char '\'' <> contents <> char '\''
diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs
index 229de12a3..b1e401fed 100644
--- a/src/Text/Pandoc/Writers/RTF.hs
+++ b/src/Text/Pandoc/Writers/RTF.hs
@@ -72,25 +72,21 @@ handleUnicode (c:cs) = if (ord c) > 127
(handleUnicode cs)
else c:(handleUnicode cs)
-escapeSpecial = backslashEscape "{\\}"
-escapeTab = substitute "\\t" "\\tab "
+-- | Escape special characters.
+escapeSpecial :: String -> String
+escapeSpecial = escapeStringUsing (('\t',"\\tab "):(backslashEscapes "{\\}"))
-- | Escape strings as needed for rich text format.
stringToRTF :: String -> String
-stringToRTF = handleUnicode . escapeSpecial . escapeTab
-
--- | 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
+stringToRTF = handleUnicode . escapeSpecial
-- | Escape things as needed for code block in RTF.
codeStringToRTF :: String -> String
-codeStringToRTF str = joinWithSep "\\line\n" (lines (stringToRTF str))
+codeStringToRTF str = joinWithSep "\\line\n" $ lines (stringToRTF str)
-- | Deal with raw LaTeX.
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.
rtfParSpaced :: Int -- ^ space after (in twips)
@@ -261,8 +257,10 @@ inlineListToRTF lst = concatMap inlineToRTF lst
inlineToRTF :: Inline -- ^ inline to convert
-> String
inlineToRTF (Emph lst) = "{\\i " ++ (inlineListToRTF lst) ++ "} "
-inlineToRTF (Strong lst) =
- "{\\b " ++ (inlineListToRTF lst) ++ "} "
+inlineToRTF (Strong 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) =
"\\u8216'" ++ (inlineListToRTF lst) ++ "\\u8217'"
inlineToRTF (Quoted DoubleQuote lst) =