aboutsummaryrefslogtreecommitdiff
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.hs24
1 files changed, 16 insertions, 8 deletions
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index f2f7438c4..d140932a7 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -1,4 +1,5 @@
-{-# LANGUAGE OverloadedStrings, ScopedTypeVariables #-}
+{-# LANGUAGE OverloadedStrings, ScopedTypeVariables,
+ PatternGuards #-}
{-
Copyright (C) 2006-2014 John MacFarlane <jgm@berkeley.edu>
@@ -37,7 +38,7 @@ import Text.Pandoc.Options
import Text.Pandoc.Templates
import Text.Printf ( printf )
import Network.URI ( isURI, unEscapeString )
-import Data.List ( (\\), isSuffixOf, isInfixOf,
+import Data.List ( (\\), isSuffixOf, isInfixOf, stripPrefix,
isPrefixOf, intercalate, intersperse )
import Data.Char ( toLower, isPunctuation, isAscii, isLetter, isDigit, ord )
import Data.Maybe ( fromMaybe )
@@ -220,6 +221,7 @@ stringToLaTeX ctx (x:xs) = do
'>' -> "\\textgreater{}" ++ rest
'[' -> "{[}" ++ rest -- to avoid interpretation as
']' -> "{]}" ++ rest -- optional arguments
+ '\'' | ctx == CodeString -> "\\textquotesingle{}" ++ rest
'\160' -> "~" ++ rest
'\x2026' -> "\\ldots{}" ++ rest
'\x2018' | ligatures -> "`" ++ rest
@@ -470,19 +472,18 @@ blockToLaTeX (Table caption aligns widths heads rows) = do
captionText <- inlineListToLaTeX caption
let capt = if isEmpty captionText
then empty
- else text "\\addlinespace"
- $$ text "\\caption" <> braces captionText
+ else text "\\caption" <> braces captionText <> "\\\\"
rows' <- mapM (tableRowToLaTeX False aligns widths) rows
let colDescriptors = text $ concat $ map toColDescriptor aligns
modify $ \s -> s{ stTable = True }
return $ "\\begin{longtable}[c]" <>
braces ("@{}" <> colDescriptors <> "@{}")
-- the @{} removes extra space at beginning and end
+ $$ capt
$$ "\\toprule\\addlinespace"
$$ headers
$$ vcat rows'
$$ "\\bottomrule"
- $$ capt
$$ "\\end{longtable}"
toColDescriptor :: Alignment -> String
@@ -742,7 +743,7 @@ inlineToLaTeX (Quoted qt lst) = do
else char '\x2018' <> inner <> char '\x2019'
inlineToLaTeX (Str str) = liftM text $ stringToLaTeX TextString str
inlineToLaTeX (Math InlineMath str) =
- return $ char '$' <> text str <> char '$'
+ return $ "\\(" <> text str <> "\\)"
inlineToLaTeX (Math DisplayMath str) =
return $ "\\[" <> text str <> "\\]"
inlineToLaTeX (RawInline f str)
@@ -757,10 +758,17 @@ inlineToLaTeX (Link txt ('#':ident, _)) = do
return $ text "\\hyperref" <> brackets (text lab) <> braces contents
inlineToLaTeX (Link txt (src, _)) =
case txt of
- [Str x] | x == src -> -- autolink
+ [Str x] | escapeURI x == src -> -- autolink
do modify $ \s -> s{ stUrl = True }
- src' <- stringToLaTeX URLString x
+ src' <- stringToLaTeX URLString src
return $ text $ "\\url{" ++ src' ++ "}"
+ [Str x] | Just rest <- stripPrefix "mailto:" src,
+ escapeURI x == rest -> -- email autolink
+ do modify $ \s -> s{ stUrl = True }
+ src' <- stringToLaTeX URLString src
+ contents <- inlineListToLaTeX txt
+ return $ "\\href" <> braces (text src') <>
+ braces ("\\nolinkurl" <> braces contents)
_ -> do contents <- inlineListToLaTeX txt
src' <- stringToLaTeX URLString src
return $ text ("\\href{" ++ src' ++ "}{") <>