2010-12-19 10:13:55 -08:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2007-11-03 23:27:58 +00:00
|
|
|
{-
|
2010-03-23 13:31:09 -07:00
|
|
|
Copyright (C) 2006-2010 John MacFarlane <jgm@berkeley.edu>
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
This program is free software; you can redistribute it and/or modify
|
|
|
|
it under the terms of the GNU General Public License as published by
|
|
|
|
the Free Software Foundation; either version 2 of the License, or
|
|
|
|
(at your option) any later version.
|
|
|
|
|
|
|
|
This program is distributed in the hope that it will be useful,
|
|
|
|
but WITHOUT ANY WARRANTY; without even the implied warranty of
|
|
|
|
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
|
|
|
GNU General Public License for more details.
|
|
|
|
|
|
|
|
You should have received a copy of the GNU General Public License
|
|
|
|
along with this program; if not, write to the Free Software
|
|
|
|
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
|
|
|
-}
|
|
|
|
|
|
|
|
{- |
|
|
|
|
Module : Text.Pandoc.Writers.LaTeX
|
2010-03-23 13:31:09 -07:00
|
|
|
Copyright : Copyright (C) 2006-2010 John MacFarlane
|
2007-11-03 23:27:58 +00:00
|
|
|
License : GNU GPL, version 2 or above
|
|
|
|
|
|
|
|
Maintainer : John MacFarlane <jgm@berkeley.edu>
|
|
|
|
Stability : alpha
|
|
|
|
Portability : portable
|
|
|
|
|
|
|
|
Conversion of 'Pandoc' format into LaTeX.
|
|
|
|
-}
|
|
|
|
module Text.Pandoc.Writers.LaTeX ( writeLaTeX ) where
|
|
|
|
import Text.Pandoc.Definition
|
2010-12-24 13:39:27 -08:00
|
|
|
import Text.Pandoc.Generic
|
2007-11-03 23:27:58 +00:00
|
|
|
import Text.Pandoc.Shared
|
2009-12-31 01:08:56 +00:00
|
|
|
import Text.Pandoc.Templates
|
2007-11-03 23:27:58 +00:00
|
|
|
import Text.Printf ( printf )
|
2011-01-14 14:45:04 -08:00
|
|
|
import Data.List ( (\\), isSuffixOf, isPrefixOf, intercalate, intersperse )
|
2010-12-15 12:06:14 +01:00
|
|
|
import Data.Char ( toLower, isPunctuation )
|
2007-11-03 23:27:58 +00:00
|
|
|
import Control.Monad.State
|
2010-12-19 10:13:55 -08:00
|
|
|
import Text.Pandoc.Pretty
|
2010-12-15 11:40:53 +01:00
|
|
|
import System.FilePath (dropExtension)
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
data WriterState =
|
2009-12-31 01:18:14 +00:00
|
|
|
WriterState { stInNote :: Bool -- @True@ if we're in a note
|
|
|
|
, 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
|
|
|
|
, stEnumerate :: Bool -- true if document needs fancy enumerated lists
|
|
|
|
, stTable :: Bool -- true if document has a table
|
|
|
|
, stStrikeout :: Bool -- true if document has strikeout
|
|
|
|
, stSubscript :: Bool -- true if document has subscript
|
|
|
|
, stUrl :: Bool -- true if document has visible URL link
|
|
|
|
, stGraphics :: Bool -- true if document contains images
|
2009-12-31 21:18:36 +00:00
|
|
|
, stLHS :: Bool -- true if document has literate haskell code
|
2010-01-03 08:47:54 +00:00
|
|
|
, stBook :: Bool -- true if document uses book or memoir class
|
2007-11-15 03:11:33 +00:00
|
|
|
}
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
-- | Convert Pandoc to LaTeX.
|
|
|
|
writeLaTeX :: WriterOptions -> Pandoc -> String
|
|
|
|
writeLaTeX options document =
|
2009-12-31 01:08:56 +00:00
|
|
|
evalState (pandocToLaTeX options document) $
|
2010-03-17 06:53:38 +00:00
|
|
|
WriterState { stInNote = False, stOLLevel = 1, stOptions = options,
|
|
|
|
stVerbInNote = False, stEnumerate = False,
|
2009-12-31 01:18:14 +00:00
|
|
|
stTable = False, stStrikeout = False, stSubscript = False,
|
2010-01-05 08:36:02 +00:00
|
|
|
stUrl = False, stGraphics = False,
|
2011-01-16 08:57:32 -08:00
|
|
|
stLHS = False, stBook = writerChapters options }
|
2007-11-03 23:27:58 +00:00
|
|
|
|
2009-12-31 01:08:56 +00:00
|
|
|
pandocToLaTeX :: WriterOptions -> Pandoc -> State WriterState String
|
|
|
|
pandocToLaTeX options (Pandoc (Meta title authors date) blocks) = do
|
2010-01-03 08:47:54 +00:00
|
|
|
let template = writerTemplate options
|
|
|
|
let usesBookClass x = "\\documentclass" `isPrefixOf` x &&
|
|
|
|
("{memoir}" `isSuffixOf` x || "{book}" `isSuffixOf` x ||
|
|
|
|
"{report}" `isSuffixOf` x)
|
|
|
|
when (any usesBookClass (lines template)) $
|
|
|
|
modify $ \s -> s{stBook = True}
|
2010-12-19 10:13:55 -08:00
|
|
|
opts <- liftM stOptions get
|
|
|
|
let colwidth = if writerWrapText opts
|
|
|
|
then Just $ writerColumns opts
|
|
|
|
else Nothing
|
|
|
|
titletext <- liftM (render colwidth) $ inlineListToLaTeX title
|
|
|
|
authorsText <- mapM (liftM (render colwidth) . inlineListToLaTeX) authors
|
|
|
|
dateText <- liftM (render colwidth) $ inlineListToLaTeX date
|
2010-12-15 13:50:21 +01:00
|
|
|
let (blocks', lastHeader) = if writerCiteMethod options == Citeproc then
|
|
|
|
(blocks, [])
|
|
|
|
else case last blocks of
|
|
|
|
Header 1 il -> (init blocks, il)
|
|
|
|
_ -> (blocks, [])
|
|
|
|
body <- blockListToLaTeX blocks'
|
2010-12-19 10:13:55 -08:00
|
|
|
biblioTitle <- liftM (render colwidth) $ inlineListToLaTeX lastHeader
|
|
|
|
let main = render colwidth body
|
2009-12-31 01:18:14 +00:00
|
|
|
st <- get
|
2010-12-15 13:50:21 +01:00
|
|
|
let biblioFiles = intercalate "," $ map dropExtension $ writerBiblioFiles options
|
2010-12-13 21:18:01 +01:00
|
|
|
citecontext = case writerCiteMethod options of
|
2010-12-15 13:50:21 +01:00
|
|
|
Natbib -> [ ("biblio-files", biblioFiles)
|
|
|
|
, ("biblio-title", biblioTitle)
|
2010-12-13 21:18:01 +01:00
|
|
|
, ("natbib", "yes")
|
|
|
|
]
|
2010-12-15 13:50:21 +01:00
|
|
|
Biblatex -> [ ("biblio-files", biblioFiles)
|
|
|
|
, ("biblio-title", biblioTitle)
|
2010-12-13 21:18:01 +01:00
|
|
|
, ("biblatex", "yes")
|
|
|
|
]
|
|
|
|
_ -> []
|
|
|
|
context = writerVariables options ++
|
2009-12-31 01:10:17 +00:00
|
|
|
[ ("toc", if writerTableOfContents options then "yes" else "")
|
2009-12-31 01:08:56 +00:00
|
|
|
, ("body", main)
|
|
|
|
, ("title", titletext)
|
2009-12-31 01:16:00 +00:00
|
|
|
, ("date", dateText) ] ++
|
2009-12-31 01:18:14 +00:00
|
|
|
[ ("author", a) | a <- authorsText ] ++
|
|
|
|
[ ("xetex", "yes") | writerXeTeX options ] ++
|
|
|
|
[ ("verbatim-in-note", "yes") | stVerbInNote st ] ++
|
|
|
|
[ ("fancy-enums", "yes") | stEnumerate st ] ++
|
|
|
|
[ ("tables", "yes") | stTable st ] ++
|
|
|
|
[ ("strikeout", "yes") | stStrikeout st ] ++
|
|
|
|
[ ("subscript", "yes") | stSubscript st ] ++
|
|
|
|
[ ("url", "yes") | stUrl st ] ++
|
2010-01-31 01:07:58 +00:00
|
|
|
[ ("numbersections", "yes") | writerNumberSections options ] ++
|
2009-12-31 21:18:36 +00:00
|
|
|
[ ("lhs", "yes") | stLHS st ] ++
|
2010-12-13 21:18:01 +01:00
|
|
|
[ ("graphics", "yes") | stGraphics st ] ++
|
2010-12-15 13:50:21 +01:00
|
|
|
[ ("book-class", "yes") | stBook st] ++
|
2011-01-17 23:54:51 +01:00
|
|
|
[ ("listings", "yes") | writerListings options ] ++
|
2010-12-13 21:18:01 +01:00
|
|
|
citecontext
|
2009-12-31 01:12:59 +00:00
|
|
|
return $ if writerStandalone options
|
2010-01-03 08:47:54 +00:00
|
|
|
then renderTemplate context template
|
2009-12-31 01:12:59 +00:00
|
|
|
else main
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
-- escape things as needed for LaTeX
|
|
|
|
|
|
|
|
stringToLaTeX :: String -> String
|
|
|
|
stringToLaTeX = escapeStringUsing latexEscapes
|
|
|
|
where latexEscapes = backslashEscapes "{}$%&_#" ++
|
|
|
|
[ ('^', "\\^{}")
|
|
|
|
, ('\\', "\\textbackslash{}")
|
|
|
|
, ('~', "\\ensuremath{\\sim}")
|
|
|
|
, ('|', "\\textbar{}")
|
|
|
|
, ('<', "\\textless{}")
|
|
|
|
, ('>', "\\textgreater{}")
|
2010-10-24 19:31:06 -07:00
|
|
|
, ('[', "{[}") -- to avoid interpretation as
|
|
|
|
, (']', "{]}") -- optional arguments
|
2008-07-11 01:24:15 +00:00
|
|
|
, ('\160', "~")
|
2010-11-27 11:53:30 -08:00
|
|
|
, ('\x2018', "`")
|
|
|
|
, ('\x2019', "'")
|
|
|
|
, ('\x201C', "``")
|
|
|
|
, ('\x201D', "''")
|
2007-11-03 23:27:58 +00:00
|
|
|
]
|
|
|
|
|
|
|
|
-- | Puts contents into LaTeX command.
|
|
|
|
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 [] = []
|
2011-01-26 20:44:25 -08:00
|
|
|
deVerb ((Code _ str):rest) =
|
2011-01-23 10:55:56 -08:00
|
|
|
(RawInline "latex" $ "\\texttt{" ++ stringToLaTeX str ++ "}"):(deVerb rest)
|
2007-11-03 23:27:58 +00:00
|
|
|
deVerb (other:rest) = other:(deVerb rest)
|
|
|
|
|
|
|
|
-- | Convert Pandoc block element to LaTeX.
|
|
|
|
blockToLaTeX :: Block -- ^ Block to convert
|
|
|
|
-> State WriterState Doc
|
|
|
|
blockToLaTeX Null = return empty
|
2010-12-19 10:13:55 -08:00
|
|
|
blockToLaTeX (Plain lst) = inlineListToLaTeX lst
|
2010-03-16 04:06:33 +00:00
|
|
|
blockToLaTeX (Para [Image txt (src,tit)]) = do
|
2011-05-24 23:56:23 -07:00
|
|
|
capt <- inlineListToLaTeX $ deVerb txt
|
2010-03-16 04:06:33 +00:00
|
|
|
img <- inlineToLaTeX (Image txt (src,tit))
|
2011-02-11 19:03:46 -08:00
|
|
|
return $ "\\begin{figure}[htbp]" $$ "\\centering" $$ img $$
|
2010-12-19 10:21:16 -08:00
|
|
|
("\\caption{" <> capt <> char '}') $$ "\\end{figure}" $$ blankline
|
2007-11-15 03:11:33 +00:00
|
|
|
blockToLaTeX (Para lst) = do
|
2010-12-19 10:13:55 -08:00
|
|
|
result <- inlineListToLaTeX lst
|
|
|
|
return $ result <> blankline
|
2007-11-03 23:27:58 +00:00
|
|
|
blockToLaTeX (BlockQuote lst) = do
|
|
|
|
contents <- blockListToLaTeX lst
|
2010-12-19 10:21:16 -08:00
|
|
|
return $ "\\begin{quote}" $$ contents $$ "\\end{quote}"
|
2011-01-17 23:54:51 +01:00
|
|
|
blockToLaTeX (CodeBlock (_,classes,keyvalAttr) str) = do
|
2007-11-03 23:27:58 +00:00
|
|
|
st <- get
|
2009-12-31 01:18:14 +00:00
|
|
|
env <- if writerLiterateHaskell (stOptions st) && "haskell" `elem` classes &&
|
2009-11-03 06:50:17 +00:00
|
|
|
"literate" `elem` classes
|
2009-12-31 21:18:36 +00:00
|
|
|
then do
|
|
|
|
modify $ \s -> s{ stLHS = True }
|
|
|
|
return "code"
|
2011-01-17 23:54:51 +01:00
|
|
|
else if writerListings (stOptions st)
|
|
|
|
then return "lstlisting"
|
|
|
|
else if stInNote st
|
|
|
|
then do
|
|
|
|
modify $ \s -> s{ stVerbInNote = True }
|
|
|
|
return "Verbatim"
|
|
|
|
else return "verbatim"
|
|
|
|
let params = if writerListings (stOptions st)
|
|
|
|
then take 1
|
|
|
|
[ "language=" ++ lang | lang <- classes
|
|
|
|
, lang `elem` ["ABAP","IDL","Plasm","ACSL","inform"
|
|
|
|
,"POV","Ada","Java","Prolog","Algol"
|
|
|
|
,"JVMIS","Promela","Ant","ksh","Python"
|
|
|
|
,"Assembler","Lisp","R","Awk","Logo"
|
|
|
|
,"Reduce","bash","make","Rexx","Basic"
|
|
|
|
,"Mathematica","RSL","C","Matlab","Ruby"
|
|
|
|
,"C++","Mercury","S","Caml","MetaPost"
|
|
|
|
,"SAS","Clean","Miranda","Scilab","Cobol"
|
|
|
|
,"Mizar","sh","Comal","ML","SHELXL","csh"
|
|
|
|
,"Modula-2","Simula","Delphi","MuPAD"
|
|
|
|
,"SQL","Eiffel","NASTRAN","tcl","Elan"
|
|
|
|
,"Oberon-2","TeX","erlang","OCL"
|
|
|
|
,"VBScript","Euphoria","Octave","Verilog"
|
|
|
|
,"Fortran","Oz","VHDL","GCL","Pascal"
|
|
|
|
,"VRML","Gnuplot","Perl","XML","Haskell"
|
|
|
|
,"PHP","XSLT","HTML","PL/I"]
|
|
|
|
] ++
|
|
|
|
[ key ++ "=" ++ attr | (key,attr) <- keyvalAttr ]
|
|
|
|
else []
|
|
|
|
printParams
|
|
|
|
| null params = empty
|
|
|
|
| otherwise = "[" <> hsep (intersperse "," (map text params)) <>
|
|
|
|
"]"
|
|
|
|
return $ "\\begin{" <> text env <> "}" <> printParams $$ flush (text str) $$
|
2010-12-19 10:13:55 -08:00
|
|
|
"\\end{" <> text env <> "}" $$ cr -- final cr needed because of footnotes
|
2011-01-24 09:05:51 -08:00
|
|
|
blockToLaTeX (RawBlock "latex" x) = return $ text x <> blankline
|
2011-01-23 10:55:56 -08:00
|
|
|
blockToLaTeX (RawBlock _ _) = return empty
|
2007-11-03 23:27:58 +00:00
|
|
|
blockToLaTeX (BulletList lst) = do
|
|
|
|
items <- mapM listItemToLaTeX lst
|
2010-12-19 10:21:16 -08:00
|
|
|
return $ "\\begin{itemize}" $$ vcat items $$ "\\end{itemize}"
|
2007-11-03 23:27:58 +00:00
|
|
|
blockToLaTeX (OrderedList (start, numstyle, numdelim) lst) = do
|
|
|
|
st <- get
|
|
|
|
let oldlevel = stOLLevel st
|
|
|
|
put $ st {stOLLevel = oldlevel + 1}
|
|
|
|
items <- mapM listItemToLaTeX lst
|
2008-07-13 16:53:06 +00:00
|
|
|
modify (\s -> s {stOLLevel = oldlevel})
|
2009-12-31 01:18:14 +00:00
|
|
|
exemplar <- if numstyle /= DefaultStyle || numdelim /= DefaultDelim
|
|
|
|
then do
|
|
|
|
modify $ \s -> s{ stEnumerate = True }
|
|
|
|
return $ char '[' <>
|
|
|
|
text (head (orderedListMarkers (1, numstyle,
|
|
|
|
numdelim))) <> char ']'
|
|
|
|
else return empty
|
2007-11-03 23:27:58 +00:00
|
|
|
let resetcounter = if start /= 1 && oldlevel <= 4
|
|
|
|
then text $ "\\setcounter{enum" ++
|
|
|
|
map toLower (toRomanNumeral oldlevel) ++
|
|
|
|
"}{" ++ show (start - 1) ++ "}"
|
|
|
|
else empty
|
2010-12-19 10:21:16 -08:00
|
|
|
return $ "\\begin{enumerate}" <> exemplar $$ resetcounter $$
|
|
|
|
vcat items $$ "\\end{enumerate}"
|
2007-11-03 23:27:58 +00:00
|
|
|
blockToLaTeX (DefinitionList lst) = do
|
|
|
|
items <- mapM defListItemToLaTeX lst
|
2010-12-19 10:21:16 -08:00
|
|
|
return $ "\\begin{description}" $$ vcat items $$ "\\end{description}"
|
2010-12-19 10:13:55 -08:00
|
|
|
blockToLaTeX HorizontalRule = return $
|
|
|
|
"\\begin{center}\\rule{3in}{0.4pt}\\end{center}" $$ blankline
|
2007-11-03 23:27:58 +00:00
|
|
|
blockToLaTeX (Header level lst) = do
|
2009-12-05 07:28:50 +00:00
|
|
|
let lst' = deVerb lst
|
|
|
|
txt <- inlineListToLaTeX lst'
|
|
|
|
let noNote (Note _) = Str ""
|
|
|
|
noNote x = x
|
2010-12-24 13:39:27 -08:00
|
|
|
let lstNoNotes = bottomUp noNote lst'
|
2009-12-05 07:28:50 +00:00
|
|
|
-- footnotes in sections don't work unless you specify an optional
|
|
|
|
-- argument: \section[mysec]{mysec\footnote{blah}}
|
|
|
|
optional <- if lstNoNotes == lst'
|
|
|
|
then return empty
|
|
|
|
else do
|
|
|
|
res <- inlineListToLaTeX lstNoNotes
|
|
|
|
return $ char '[' <> res <> char ']'
|
2010-01-03 08:47:54 +00:00
|
|
|
let stuffing = optional <> char '{' <> txt <> char '}'
|
|
|
|
book <- liftM stBook get
|
2010-12-18 15:05:21 -08:00
|
|
|
let level' = if book then level - 1 else level
|
2010-12-19 10:13:55 -08:00
|
|
|
let headerWith x y = text x <> y $$ blankline
|
2010-12-18 15:05:21 -08:00
|
|
|
return $ case level' of
|
|
|
|
0 -> headerWith "\\chapter" stuffing
|
|
|
|
1 -> headerWith "\\section" stuffing
|
|
|
|
2 -> headerWith "\\subsection" stuffing
|
|
|
|
3 -> headerWith "\\subsubsection" stuffing
|
|
|
|
4 -> headerWith "\\paragraph" stuffing
|
|
|
|
5 -> headerWith "\\subparagraph" stuffing
|
2010-12-19 10:13:55 -08:00
|
|
|
_ -> txt $$ blankline
|
2007-11-03 23:27:58 +00:00
|
|
|
blockToLaTeX (Table caption aligns widths heads rows) = do
|
2010-03-01 02:28:03 +00:00
|
|
|
headers <- if all null heads
|
|
|
|
then return empty
|
2011-07-10 09:09:51 -07:00
|
|
|
else liftM ($$ "\\hline\\noalign{\\smallskip}")
|
|
|
|
$ (tableRowToLaTeX widths) heads
|
2011-05-24 23:56:23 -07:00
|
|
|
captionText <- inlineListToLaTeX $ deVerb caption
|
2011-01-14 14:45:04 -08:00
|
|
|
rows' <- mapM (tableRowToLaTeX widths) rows
|
2009-11-28 03:22:33 +00:00
|
|
|
let colDescriptors = concat $ zipWith toColDescriptor widths aligns
|
2007-11-03 23:27:58 +00:00
|
|
|
let tableBody = text ("\\begin{tabular}{" ++ colDescriptors ++ "}") $$
|
2010-12-19 10:21:16 -08:00
|
|
|
headers $$ vcat rows' $$ "\\end{tabular}"
|
|
|
|
let centered txt = "\\begin{center}" $$ txt $$ "\\end{center}"
|
2009-12-31 01:18:14 +00:00
|
|
|
modify $ \s -> s{ stTable = True }
|
2007-11-03 23:27:58 +00:00
|
|
|
return $ if isEmpty captionText
|
2010-12-19 10:13:55 -08:00
|
|
|
then centered tableBody $$ blankline
|
2010-12-19 10:21:16 -08:00
|
|
|
else "\\begin{table}[h]" $$ centered tableBody $$
|
|
|
|
inCmd "caption" captionText $$ "\\end{table}" $$ blankline
|
2007-11-03 23:27:58 +00:00
|
|
|
|
2009-11-28 03:22:33 +00:00
|
|
|
toColDescriptor :: Double -> Alignment -> String
|
|
|
|
toColDescriptor 0 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") ++
|
2011-01-14 14:45:04 -08:00
|
|
|
"\\hspace{0pt}}p{" ++ printf "%.2f" width ++ "\\columnwidth}"
|
2009-11-28 03:22:33 +00:00
|
|
|
|
2008-07-13 16:53:06 +00:00
|
|
|
blockListToLaTeX :: [Block] -> State WriterState Doc
|
2007-11-03 23:27:58 +00:00
|
|
|
blockListToLaTeX lst = mapM blockToLaTeX lst >>= return . vcat
|
|
|
|
|
2011-01-14 14:45:04 -08:00
|
|
|
tableRowToLaTeX :: [Double] -> [[Block]] -> State WriterState Doc
|
|
|
|
tableRowToLaTeX widths cols = do
|
|
|
|
renderedCells <- mapM blockListToLaTeX cols
|
|
|
|
let toCell 0 c = c
|
2011-07-10 09:09:51 -07:00
|
|
|
toCell w c = "\\parbox[t]{" <> text (printf "%.2f" w) <>
|
2011-01-14 14:45:04 -08:00
|
|
|
"\\columnwidth}{" <> c <> cr <> "}"
|
|
|
|
let cells = zipWith toCell widths renderedCells
|
2011-07-10 09:09:51 -07:00
|
|
|
return $ (hcat $ intersperse (" & ") cells) <> "\\\\\\noalign{\\medskip}"
|
2007-11-03 23:27:58 +00:00
|
|
|
|
2008-07-13 16:53:06 +00:00
|
|
|
listItemToLaTeX :: [Block] -> State WriterState Doc
|
2008-08-09 16:50:46 +00:00
|
|
|
listItemToLaTeX lst = blockListToLaTeX lst >>= return . (text "\\item" $$) .
|
2007-11-03 23:27:58 +00:00
|
|
|
(nest 2)
|
|
|
|
|
2009-12-07 08:26:53 +00:00
|
|
|
defListItemToLaTeX :: ([Inline], [[Block]]) -> State WriterState Doc
|
|
|
|
defListItemToLaTeX (term, defs) = do
|
2007-11-03 23:27:58 +00:00
|
|
|
term' <- inlineListToLaTeX $ deVerb term
|
2010-12-19 10:13:55 -08:00
|
|
|
def' <- liftM vsep $ mapM blockListToLaTeX defs
|
2010-12-19 10:21:16 -08:00
|
|
|
return $ "\\item" <> brackets term' $$ def'
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
-- | Convert list of inline elements to LaTeX.
|
|
|
|
inlineListToLaTeX :: [Inline] -- ^ Inlines to convert
|
|
|
|
-> State WriterState Doc
|
|
|
|
inlineListToLaTeX lst = mapM inlineToLaTeX lst >>= return . hcat
|
|
|
|
|
|
|
|
isQuoted :: Inline -> Bool
|
|
|
|
isQuoted (Quoted _ _) = True
|
|
|
|
isQuoted Apostrophe = True
|
|
|
|
isQuoted _ = False
|
|
|
|
|
|
|
|
-- | Convert inline element to LaTeX
|
|
|
|
inlineToLaTeX :: Inline -- ^ Inline to convert
|
|
|
|
-> State WriterState Doc
|
|
|
|
inlineToLaTeX (Emph lst) =
|
|
|
|
inlineListToLaTeX (deVerb lst) >>= return . inCmd "emph"
|
|
|
|
inlineToLaTeX (Strong lst) =
|
|
|
|
inlineListToLaTeX (deVerb lst) >>= return . inCmd "textbf"
|
|
|
|
inlineToLaTeX (Strikeout lst) = do
|
|
|
|
contents <- inlineListToLaTeX $ deVerb lst
|
2009-12-31 01:18:14 +00:00
|
|
|
modify $ \s -> s{ stStrikeout = True }
|
2007-11-03 23:27:58 +00:00
|
|
|
return $ inCmd "sout" contents
|
2009-12-31 01:18:14 +00:00
|
|
|
inlineToLaTeX (Superscript lst) =
|
2007-11-03 23:27:58 +00:00
|
|
|
inlineListToLaTeX (deVerb lst) >>= return . inCmd "textsuperscript"
|
|
|
|
inlineToLaTeX (Subscript lst) = do
|
2009-12-31 01:18:14 +00:00
|
|
|
modify $ \s -> s{ stSubscript = True }
|
2007-11-03 23:27:58 +00:00
|
|
|
contents <- inlineListToLaTeX $ deVerb lst
|
|
|
|
-- oddly, latex includes \textsuperscript but not \textsubscript
|
2008-06-08 03:29:09 +00:00
|
|
|
-- so we have to define it (using a different name so as not to conflict with memoir class):
|
|
|
|
return $ inCmd "textsubscr" contents
|
2008-07-15 23:26:06 +00:00
|
|
|
inlineToLaTeX (SmallCaps lst) =
|
|
|
|
inlineListToLaTeX (deVerb lst) >>= return . inCmd "textsc"
|
2010-12-13 21:18:01 +01:00
|
|
|
inlineToLaTeX (Cite cits lst) = do
|
|
|
|
st <- get
|
|
|
|
let opts = stOptions st
|
|
|
|
case writerCiteMethod opts of
|
|
|
|
Natbib -> citationsToNatbib cits
|
|
|
|
Biblatex -> citationsToBiblatex cits
|
|
|
|
_ -> inlineListToLaTeX lst
|
|
|
|
|
2011-01-26 20:44:25 -08:00
|
|
|
inlineToLaTeX (Code _ str) = do
|
2009-12-31 01:18:14 +00:00
|
|
|
st <- get
|
|
|
|
when (stInNote st) $ modify $ \s -> s{ stVerbInNote = True }
|
2007-11-03 23:27:58 +00:00
|
|
|
let chr = ((enumFromTo '!' '~') \\ str) !! 0
|
2011-01-17 23:54:51 +01:00
|
|
|
if writerListings (stOptions st)
|
|
|
|
then return $ text $ "\\lstinline" ++ [chr] ++ str ++ [chr]
|
|
|
|
else return $ text $ "\\verb" ++ [chr] ++ str ++ [chr]
|
2007-11-03 23:27:58 +00:00
|
|
|
inlineToLaTeX (Quoted SingleQuote lst) = do
|
|
|
|
contents <- inlineListToLaTeX lst
|
|
|
|
let s1 = if (not (null lst)) && (isQuoted (head lst))
|
2010-12-19 10:21:16 -08:00
|
|
|
then "\\,"
|
|
|
|
else empty
|
2007-11-03 23:27:58 +00:00
|
|
|
let s2 = if (not (null lst)) && (isQuoted (last lst))
|
2010-12-19 10:21:16 -08:00
|
|
|
then "\\,"
|
2007-11-03 23:27:58 +00:00
|
|
|
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))
|
2010-12-19 10:21:16 -08:00
|
|
|
then "\\,"
|
|
|
|
else empty
|
2007-11-03 23:27:58 +00:00
|
|
|
let s2 = if (not (null lst)) && (isQuoted (last lst))
|
2010-12-19 10:21:16 -08:00
|
|
|
then "\\,"
|
2007-11-03 23:27:58 +00:00
|
|
|
else empty
|
2010-12-19 10:21:16 -08:00
|
|
|
return $ "``" <> s1 <> contents <> s2 <> "''"
|
2007-11-03 23:27:58 +00:00
|
|
|
inlineToLaTeX Apostrophe = return $ char '\''
|
2010-12-19 10:21:16 -08:00
|
|
|
inlineToLaTeX EmDash = return "---"
|
|
|
|
inlineToLaTeX EnDash = return "--"
|
|
|
|
inlineToLaTeX Ellipses = return "\\ldots{}"
|
2007-11-03 23:27:58 +00:00
|
|
|
inlineToLaTeX (Str str) = return $ text $ stringToLaTeX str
|
2008-08-13 03:02:42 +00:00
|
|
|
inlineToLaTeX (Math InlineMath str) = return $ char '$' <> text str <> char '$'
|
2010-12-19 10:21:16 -08:00
|
|
|
inlineToLaTeX (Math DisplayMath str) = return $ "\\[" <> text str <> "\\]"
|
2011-01-23 10:55:56 -08:00
|
|
|
inlineToLaTeX (RawInline "latex" str) = return $ text str
|
2011-01-24 22:13:27 -08:00
|
|
|
inlineToLaTeX (RawInline "tex" str) = return $ text str
|
2011-01-23 10:55:56 -08:00
|
|
|
inlineToLaTeX (RawInline _ _) = return empty
|
2010-12-19 10:21:16 -08:00
|
|
|
inlineToLaTeX (LineBreak) = return "\\\\"
|
2010-12-19 10:13:55 -08:00
|
|
|
inlineToLaTeX Space = return space
|
2010-01-05 08:36:02 +00:00
|
|
|
inlineToLaTeX (Link txt (src, _)) =
|
2007-11-03 23:27:58 +00:00
|
|
|
case txt of
|
2011-01-26 20:44:25 -08:00
|
|
|
[Code _ x] | x == src -> -- autolink
|
2009-12-31 01:18:14 +00:00
|
|
|
do modify $ \s -> s{ stUrl = True }
|
|
|
|
return $ text $ "\\url{" ++ x ++ "}"
|
2007-11-03 23:27:58 +00:00
|
|
|
_ -> do contents <- inlineListToLaTeX $ deVerb txt
|
2011-01-14 18:59:50 -08:00
|
|
|
return $ text ("\\href{" ++ stringToLaTeX src ++ "}{") <>
|
|
|
|
contents <> char '}'
|
2009-12-31 01:18:14 +00:00
|
|
|
inlineToLaTeX (Image _ (source, _)) = do
|
|
|
|
modify $ \s -> s{ stGraphics = True }
|
2010-12-19 10:21:16 -08:00
|
|
|
return $ "\\includegraphics" <> braces (text source)
|
2007-11-03 23:27:58 +00:00
|
|
|
inlineToLaTeX (Note contents) = do
|
2010-12-19 10:13:55 -08:00
|
|
|
modify (\s -> s{stInNote = True})
|
2007-11-03 23:27:58 +00:00
|
|
|
contents' <- blockListToLaTeX contents
|
2008-07-13 16:53:06 +00:00
|
|
|
modify (\s -> s {stInNote = False})
|
2007-11-03 23:27:58 +00:00
|
|
|
-- note: a \n before } is needed when note ends with a Verbatim environment
|
2010-12-19 10:21:16 -08:00
|
|
|
return $ "\\footnote" <> braces (nest 2 contents')
|
2010-12-13 21:18:01 +01:00
|
|
|
|
|
|
|
|
|
|
|
citationsToNatbib :: [Citation] -> State WriterState Doc
|
|
|
|
citationsToNatbib (one:[])
|
|
|
|
= citeCommand c p s k
|
|
|
|
where
|
|
|
|
Citation { citationId = k
|
|
|
|
, citationPrefix = p
|
|
|
|
, citationSuffix = s
|
|
|
|
, citationMode = m
|
|
|
|
}
|
|
|
|
= one
|
|
|
|
c = case m of
|
|
|
|
AuthorInText -> "citet"
|
|
|
|
SuppressAuthor -> "citeyearpar"
|
|
|
|
NormalCitation -> "citep"
|
|
|
|
|
|
|
|
citationsToNatbib cits
|
|
|
|
| noPrefix (tail cits) && noSuffix (init cits) && ismode NormalCitation cits
|
|
|
|
= citeCommand "citep" p s ks
|
|
|
|
where
|
|
|
|
noPrefix = and . map (null . citationPrefix)
|
|
|
|
noSuffix = and . map (null . citationSuffix)
|
|
|
|
ismode m = and . map (((==) m) . citationMode)
|
|
|
|
p = citationPrefix $ head $ cits
|
|
|
|
s = citationSuffix $ last $ cits
|
|
|
|
ks = intercalate ", " $ map citationId cits
|
|
|
|
|
|
|
|
citationsToNatbib (c:cs) | citationMode c == AuthorInText = do
|
|
|
|
author <- citeCommand "citeauthor" [] [] (citationId c)
|
|
|
|
cits <- citationsToNatbib (c { citationMode = SuppressAuthor } : cs)
|
|
|
|
return $ author <+> cits
|
|
|
|
|
|
|
|
citationsToNatbib cits = do
|
|
|
|
cits' <- mapM convertOne cits
|
|
|
|
return $ text "\\citetext{" <> foldl combineTwo empty cits' <> text "}"
|
|
|
|
where
|
|
|
|
combineTwo a b | isEmpty a = b
|
|
|
|
| otherwise = a <> text "; " <> b
|
|
|
|
convertOne Citation { citationId = k
|
|
|
|
, citationPrefix = p
|
|
|
|
, citationSuffix = s
|
|
|
|
, citationMode = m
|
|
|
|
}
|
|
|
|
= case m of
|
|
|
|
AuthorInText -> citeCommand "citealt" p s k
|
|
|
|
SuppressAuthor -> citeCommand "citeyear" p s k
|
|
|
|
NormalCitation -> citeCommand "citealp" p s k
|
|
|
|
|
|
|
|
citeCommand :: String -> [Inline] -> [Inline] -> String -> State WriterState Doc
|
|
|
|
citeCommand c p s k = do
|
|
|
|
args <- citeArguments p s k
|
|
|
|
return $ text ("\\" ++ c) <> args
|
|
|
|
|
|
|
|
citeArguments :: [Inline] -> [Inline] -> String -> State WriterState Doc
|
|
|
|
citeArguments p s k = do
|
2010-12-15 12:06:14 +01:00
|
|
|
let s' = case s of
|
|
|
|
(Str (x:[]) : r) | isPunctuation x -> dropWhile (== Space) r
|
|
|
|
(Str (x:xs) : r) | isPunctuation x -> Str xs : r
|
|
|
|
_ -> s
|
2010-12-13 21:18:01 +01:00
|
|
|
pdoc <- inlineListToLaTeX p
|
2010-12-15 12:06:14 +01:00
|
|
|
sdoc <- inlineListToLaTeX s'
|
2010-12-13 21:18:01 +01:00
|
|
|
let optargs = case (isEmpty pdoc, isEmpty sdoc) of
|
|
|
|
(True, True ) -> empty
|
|
|
|
(True, False) -> brackets sdoc
|
|
|
|
(_ , _ ) -> brackets pdoc <> brackets sdoc
|
|
|
|
return $ optargs <> braces (text k)
|
|
|
|
|
|
|
|
citationsToBiblatex :: [Citation] -> State WriterState Doc
|
|
|
|
citationsToBiblatex (one:[])
|
|
|
|
= citeCommand cmd p s k
|
|
|
|
where
|
|
|
|
Citation { citationId = k
|
|
|
|
, citationPrefix = p
|
|
|
|
, citationSuffix = s
|
|
|
|
, citationMode = m
|
|
|
|
} = one
|
|
|
|
cmd = case m of
|
|
|
|
SuppressAuthor -> "autocite*"
|
|
|
|
AuthorInText -> "textcite"
|
|
|
|
NormalCitation -> "autocite"
|
|
|
|
|
|
|
|
citationsToBiblatex (c:cs) = do
|
|
|
|
args <- mapM convertOne (c:cs)
|
|
|
|
return $ text cmd <> foldl (<>) empty args
|
|
|
|
where
|
|
|
|
cmd = case citationMode c of
|
|
|
|
AuthorInText -> "\\textcites"
|
|
|
|
_ -> "\\autocites"
|
|
|
|
convertOne Citation { citationId = k
|
|
|
|
, citationPrefix = p
|
|
|
|
, citationSuffix = s
|
|
|
|
}
|
|
|
|
= citeArguments p s k
|
|
|
|
|
|
|
|
citationsToBiblatex _ = return empty
|