summaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/LaTeX.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers/LaTeX.hs')
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs187
1 files changed, 111 insertions, 76 deletions
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 7dd736da4..d925b2897 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -34,7 +34,9 @@ import Text.Pandoc.Generic
import Text.Pandoc.Shared
import Text.Pandoc.Templates
import Text.Printf ( printf )
-import Data.List ( (\\), isSuffixOf, isPrefixOf, intercalate, intersperse )
+import Network.URI ( isAbsoluteURI, unEscapeString )
+import Data.List ( (\\), isSuffixOf, isInfixOf,
+ isPrefixOf, intercalate, intersperse )
import Data.Char ( toLower, isPunctuation )
import Control.Monad.State
import Text.Pandoc.Pretty
@@ -42,6 +44,9 @@ import System.FilePath (dropExtension)
data WriterState =
WriterState { stInNote :: Bool -- @True@ if we're in a note
+ , stInTable :: Bool -- @True@ if we're in a table
+ , stTableNotes :: [(Char, Doc)] -- List of markers, notes
+ -- in current table
, stOLLevel :: Int -- level of ordered list nesting
, stOptions :: WriterOptions -- writer options, so they don't have to be parameter
, stVerbInNote :: Bool -- true if document has verbatim text in note
@@ -53,17 +58,20 @@ data WriterState =
, stGraphics :: Bool -- true if document contains images
, stLHS :: Bool -- true if document has literate haskell code
, stBook :: Bool -- true if document uses book or memoir class
+ , stCsquotes :: Bool -- true if document uses csquotes
}
-- | Convert Pandoc to LaTeX.
writeLaTeX :: WriterOptions -> Pandoc -> String
writeLaTeX options document =
evalState (pandocToLaTeX options document) $
- WriterState { stInNote = False, stOLLevel = 1, stOptions = options,
+ WriterState { stInNote = False, stInTable = False,
+ stTableNotes = [], stOLLevel = 1, stOptions = options,
stVerbInNote = False, stEnumerate = False,
stTable = False, stStrikeout = False, stSubscript = False,
stUrl = False, stGraphics = False,
- stLHS = False, stBook = writerChapters options }
+ stLHS = False, stBook = writerChapters options,
+ stCsquotes = False }
pandocToLaTeX :: WriterOptions -> Pandoc -> State WriterState String
pandocToLaTeX options (Pandoc (Meta title authors date) blocks) = do
@@ -73,6 +81,10 @@ pandocToLaTeX options (Pandoc (Meta title authors date) blocks) = do
"{report}" `isSuffixOf` x)
when (any usesBookClass (lines template)) $
modify $ \s -> s{stBook = True}
+ -- check for \usepackage...{csquotes}; if present, we'll use
+ -- \enquote{...} for smart quotes:
+ when ("{csquotes}" `isInfixOf` template) $
+ modify $ \s -> s{stCsquotes = True}
opts <- liftM stOptions get
let colwidth = if writerWrapText opts
then Just $ writerColumns opts
@@ -106,7 +118,6 @@ pandocToLaTeX options (Pandoc (Meta title authors date) blocks) = do
, ("title", titletext)
, ("date", dateText) ] ++
[ ("author", a) | a <- authorsText ] ++
- [ ("xetex", "yes") | writerXeTeX options ] ++
[ ("verbatim-in-note", "yes") | stVerbInNote st ] ++
[ ("fancy-enums", "yes") | stEnumerate st ] ++
[ ("tables", "yes") | stTable st ] ++
@@ -147,14 +158,6 @@ stringToLaTeX = escapeStringUsing latexEscapes
inCmd :: String -> Doc -> Doc
inCmd cmd contents = char '\\' <> text cmd <> braces contents
--- | Remove all code elements from list of inline elements
--- (because it's illegal to have verbatim inside some command arguments)
-deVerb :: [Inline] -> [Inline]
-deVerb [] = []
-deVerb ((Code _ str):rest) =
- (RawInline "latex" $ "\\texttt{" ++ stringToLaTeX str ++ "}"):(deVerb rest)
-deVerb (other:rest) = other:(deVerb rest)
-
-- | Convert Pandoc block element to LaTeX.
blockToLaTeX :: Block -- ^ Block to convert
-> State WriterState Doc
@@ -211,8 +214,9 @@ blockToLaTeX (CodeBlock (_,classes,keyvalAttr) str) = do
| null params = empty
| otherwise = "[" <> hsep (intersperse "," (map text params)) <>
"]"
- return $ "\\begin{" <> text env <> "}" <> printParams $$ flush (text str) $$
- "\\end{" <> text env <> "}" $$ cr -- final cr needed because of footnotes
+ return $ flush ("\\begin{" <> text env <> "}" <> printParams $$ text str $$
+ "\\end{" <> text env <> "}") $$ cr
+ -- final cr needed because of footnotes
blockToLaTeX (RawBlock "latex" x) = return $ text x <> blankline
blockToLaTeX (RawBlock _ _) = return empty
blockToLaTeX (BulletList lst) = do
@@ -244,14 +248,13 @@ blockToLaTeX (DefinitionList lst) = do
blockToLaTeX HorizontalRule = return $
"\\begin{center}\\rule{3in}{0.4pt}\\end{center}" $$ blankline
blockToLaTeX (Header level lst) = do
- let lst' = deVerb lst
- txt <- inlineListToLaTeX lst'
+ txt <- inlineListToLaTeX lst
let noNote (Note _) = Str ""
noNote x = x
- let lstNoNotes = bottomUp noNote lst'
+ let lstNoNotes = bottomUp noNote lst
-- footnotes in sections don't work unless you specify an optional
-- argument: \section[mysec]{mysec\footnote{blah}}
- optional <- if lstNoNotes == lst'
+ optional <- if lstNoNotes == lst
then return empty
else do
res <- inlineListToLaTeX lstNoNotes
@@ -269,47 +272,61 @@ blockToLaTeX (Header level lst) = do
5 -> headerWith "\\subparagraph" stuffing
_ -> txt $$ blankline
blockToLaTeX (Table caption aligns widths heads rows) = do
+ modify $ \s -> s{ stInTable = True, stTableNotes = [] }
headers <- if all null heads
then return empty
- else liftM ($$ "\\hline") $ (tableRowToLaTeX widths) heads
+ else liftM ($$ "\\ML")
+ $ (tableRowToLaTeX True aligns widths) heads
captionText <- inlineListToLaTeX caption
- rows' <- mapM (tableRowToLaTeX widths) rows
- let colDescriptors = concat $ zipWith toColDescriptor widths aligns
- let tableBody = text ("\\begin{tabular}{" ++ colDescriptors ++ "}") $$
- headers $$ vcat rows' $$ "\\end{tabular}"
- let centered txt = "\\begin{center}" $$ txt $$ "\\end{center}"
- modify $ \s -> s{ stTable = True }
- return $ if isEmpty captionText
- then centered tableBody $$ blankline
- else "\\begin{table}[h]" $$ centered tableBody $$
- inCmd "caption" captionText $$ "\\end{table}" $$ blankline
-
-toColDescriptor :: Double -> Alignment -> String
-toColDescriptor 0 align =
+ let capt = if isEmpty captionText
+ then empty
+ else text "caption = " <> captionText <> "," <> space
+ rows' <- mapM (tableRowToLaTeX False aligns widths) rows
+ let rows'' = intersperse ("\\\\\\noalign{\\medskip}") rows'
+ tableNotes <- liftM (reverse . stTableNotes) get
+ let toNote (marker, x) = "\\tnote" <> brackets (char marker) <>
+ braces (nest 2 x)
+ let notes = vcat $ map toNote tableNotes
+ let colDescriptors = text $ concat $ map toColDescriptor aligns
+ let tableBody =
+ ("\\ctable" <> brackets (capt <> text "pos = H, center, botcap"))
+ <> braces colDescriptors
+ $$ braces ("% notes" <> cr <> notes <> cr)
+ $$ braces (text "% rows" $$ "\\FL" $$
+ vcat (headers : rows'') $$ "\\LL" <> cr)
+ modify $ \s -> s{ stTable = True, stInTable = False, stTableNotes = [] }
+ return $ tableBody $$ blankline
+
+toColDescriptor :: Alignment -> String
+toColDescriptor align =
case align of
AlignLeft -> "l"
AlignRight -> "r"
AlignCenter -> "c"
AlignDefault -> "l"
-toColDescriptor width align = ">{\\PBS" ++
- (case align of
- AlignLeft -> "\\raggedright"
- AlignRight -> "\\raggedleft"
- AlignCenter -> "\\centering"
- AlignDefault -> "\\raggedright") ++
- "\\hspace{0pt}}p{" ++ printf "%.2f" width ++ "\\columnwidth}"
blockListToLaTeX :: [Block] -> State WriterState Doc
blockListToLaTeX lst = mapM blockToLaTeX lst >>= return . vcat
-tableRowToLaTeX :: [Double] -> [[Block]] -> State WriterState Doc
-tableRowToLaTeX widths cols = do
+tableRowToLaTeX :: Bool
+ -> [Alignment]
+ -> [Double]
+ -> [[Block]]
+ -> State WriterState Doc
+tableRowToLaTeX header aligns widths cols = do
renderedCells <- mapM blockListToLaTeX cols
- let toCell 0 c = c
- toCell w c = "\\parbox{" <> text (printf "%.2f" w) <>
- "\\columnwidth}{" <> c <> cr <> "}"
- let cells = zipWith toCell widths renderedCells
- return $ (hcat $ intersperse (" & ") cells) <> "\\\\"
+ let valign = text $ if header then "[b]" else "[t]"
+ let halign x = case x of
+ AlignLeft -> "\\raggedright"
+ AlignRight -> "\\raggedleft"
+ AlignCenter -> "\\centering"
+ AlignDefault -> "\\raggedright"
+ let toCell 0 _ c = c
+ toCell w a c = "\\parbox" <> valign <>
+ braces (text (printf "%.2f\\columnwidth" w)) <>
+ braces (halign a <> cr <> c <> cr)
+ let cells = zipWith3 toCell widths aligns renderedCells
+ return $ hcat $ intersperse (" & ") cells
listItemToLaTeX :: [Block] -> State WriterState Doc
listItemToLaTeX lst = blockListToLaTeX lst >>= return . (text "\\item" $$) .
@@ -317,7 +334,7 @@ listItemToLaTeX lst = blockListToLaTeX lst >>= return . (text "\\item" $$) .
defListItemToLaTeX :: ([Inline], [[Block]]) -> State WriterState Doc
defListItemToLaTeX (term, defs) = do
- term' <- inlineListToLaTeX $ deVerb term
+ term' <- inlineListToLaTeX term
def' <- liftM vsep $ mapM blockListToLaTeX defs
return $ "\\item" <> brackets term' $$ def'
@@ -335,23 +352,23 @@ isQuoted _ = False
inlineToLaTeX :: Inline -- ^ Inline to convert
-> State WriterState Doc
inlineToLaTeX (Emph lst) =
- inlineListToLaTeX (deVerb lst) >>= return . inCmd "emph"
+ inlineListToLaTeX lst >>= return . inCmd "emph"
inlineToLaTeX (Strong lst) =
- inlineListToLaTeX (deVerb lst) >>= return . inCmd "textbf"
+ inlineListToLaTeX lst >>= return . inCmd "textbf"
inlineToLaTeX (Strikeout lst) = do
- contents <- inlineListToLaTeX $ deVerb lst
+ contents <- inlineListToLaTeX lst
modify $ \s -> s{ stStrikeout = True }
return $ inCmd "sout" contents
inlineToLaTeX (Superscript lst) =
- inlineListToLaTeX (deVerb lst) >>= return . inCmd "textsuperscript"
+ inlineListToLaTeX lst >>= return . inCmd "textsuperscript"
inlineToLaTeX (Subscript lst) = do
modify $ \s -> s{ stSubscript = True }
- contents <- inlineListToLaTeX $ deVerb lst
+ contents <- inlineListToLaTeX lst
-- oddly, latex includes \textsuperscript but not \textsubscript
-- so we have to define it (using a different name so as not to conflict with memoir class):
return $ inCmd "textsubscr" contents
inlineToLaTeX (SmallCaps lst) =
- inlineListToLaTeX (deVerb lst) >>= return . inCmd "textsc"
+ inlineListToLaTeX lst >>= return . inCmd "textsc"
inlineToLaTeX (Cite cits lst) = do
st <- get
let opts = stOptions st
@@ -362,29 +379,38 @@ inlineToLaTeX (Cite cits lst) = do
inlineToLaTeX (Code _ str) = do
st <- get
- when (stInNote st) $ modify $ \s -> s{ stVerbInNote = True }
- let chr = ((enumFromTo '!' '~') \\ str) !! 0
if writerListings (stOptions st)
- then return $ text $ "\\lstinline" ++ [chr] ++ str ++ [chr]
- else return $ text $ "\\verb" ++ [chr] ++ str ++ [chr]
+ then do
+ when (stInNote st) $ modify $ \s -> s{ stVerbInNote = True }
+ let chr = ((enumFromTo '!' '~') \\ str) !! 0
+ return $ text $ "\\lstinline" ++ [chr] ++ str ++ [chr]
+ else return $ text $ "\\texttt{" ++ stringToLaTeX str ++ "}"
inlineToLaTeX (Quoted SingleQuote lst) = do
contents <- inlineListToLaTeX lst
- let s1 = if (not (null lst)) && (isQuoted (head lst))
- then "\\,"
- else empty
- let s2 = if (not (null lst)) && (isQuoted (last lst))
- then "\\,"
- else empty
- return $ char '`' <> s1 <> contents <> s2 <> char '\''
+ csquotes <- liftM stCsquotes get
+ if csquotes
+ then return $ "\\enquote" <> braces contents
+ else do
+ let s1 = if (not (null lst)) && (isQuoted (head lst))
+ then "\\,"
+ else empty
+ let s2 = if (not (null lst)) && (isQuoted (last lst))
+ then "\\,"
+ else empty
+ return $ char '`' <> s1 <> contents <> s2 <> char '\''
inlineToLaTeX (Quoted DoubleQuote lst) = do
contents <- inlineListToLaTeX lst
- let s1 = if (not (null lst)) && (isQuoted (head lst))
- then "\\,"
- else empty
- let s2 = if (not (null lst)) && (isQuoted (last lst))
- then "\\,"
- else empty
- return $ "``" <> s1 <> contents <> s2 <> "''"
+ csquotes <- liftM stCsquotes get
+ if csquotes
+ then return $ "\\enquote" <> braces contents
+ else do
+ let s1 = if (not (null lst)) && (isQuoted (head lst))
+ then "\\,"
+ else empty
+ let s2 = if (not (null lst)) && (isQuoted (last lst))
+ then "\\,"
+ else empty
+ return $ "``" <> s1 <> contents <> s2 <> "''"
inlineToLaTeX Apostrophe = return $ char '\''
inlineToLaTeX EmDash = return "---"
inlineToLaTeX EnDash = return "--"
@@ -402,19 +428,28 @@ inlineToLaTeX (Link txt (src, _)) =
[Code _ x] | x == src -> -- autolink
do modify $ \s -> s{ stUrl = True }
return $ text $ "\\url{" ++ x ++ "}"
- _ -> do contents <- inlineListToLaTeX $ deVerb txt
+ _ -> do contents <- inlineListToLaTeX txt
return $ text ("\\href{" ++ stringToLaTeX src ++ "}{") <>
contents <> char '}'
inlineToLaTeX (Image _ (source, _)) = do
modify $ \s -> s{ stGraphics = True }
- return $ "\\includegraphics" <> braces (text source)
+ let source' = if isAbsoluteURI source
+ then source
+ else unEscapeString source
+ return $ "\\includegraphics" <> braces (text source')
inlineToLaTeX (Note contents) = do
modify (\s -> s{stInNote = True})
contents' <- blockListToLaTeX contents
modify (\s -> s {stInNote = False})
- -- note: a \n before } is needed when note ends with a Verbatim environment
- return $ "\\footnote" <> braces (nest 2 contents')
-
+ inTable <- liftM stInTable get
+ if inTable
+ then do
+ curnotes <- liftM stTableNotes get
+ let marker = cycle ['a'..'z'] !! length curnotes
+ modify $ \s -> s{ stTableNotes = (marker, contents') : curnotes }
+ return $ "\\tmark" <> brackets (char marker) <> space
+ else return $ "\\footnote" <> braces (nest 2 contents')
+ -- note: a \n before } needed when note ends with a Verbatim environment
citationsToNatbib :: [Citation] -> State WriterState Doc
citationsToNatbib (one:[])