2013-05-10 22:53:35 -07:00
|
|
|
{-# LANGUAGE OverloadedStrings, ScopedTypeVariables #-}
|
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
|
2011-12-23 18:05:14 -08:00
|
|
|
License : GNU GPL, version 2 or above
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
Maintainer : John MacFarlane <jgm@berkeley.edu>
|
2011-12-23 18:05:14 -08:00
|
|
|
Stability : alpha
|
2007-11-03 23:27:58 +00:00
|
|
|
Portability : portable
|
|
|
|
|
|
|
|
Conversion of 'Pandoc' format into LaTeX.
|
|
|
|
-}
|
|
|
|
module Text.Pandoc.Writers.LaTeX ( writeLaTeX ) where
|
|
|
|
import Text.Pandoc.Definition
|
2013-08-10 18:13:38 -07:00
|
|
|
import Text.Pandoc.Walk
|
2007-11-03 23:27:58 +00:00
|
|
|
import Text.Pandoc.Shared
|
2013-07-01 20:47:26 -07:00
|
|
|
import Text.Pandoc.Writers.Shared
|
2012-07-26 22:59:56 -07:00
|
|
|
import Text.Pandoc.Options
|
2009-12-31 01:08:56 +00:00
|
|
|
import Text.Pandoc.Templates
|
2007-11-03 23:27:58 +00:00
|
|
|
import Text.Printf ( printf )
|
2013-10-16 09:48:11 -07:00
|
|
|
import Network.URI ( isURI, unEscapeString )
|
2011-07-23 13:11:39 -07:00
|
|
|
import Data.List ( (\\), isSuffixOf, isInfixOf,
|
|
|
|
isPrefixOf, intercalate, intersperse )
|
2013-10-17 22:06:39 -07:00
|
|
|
import Data.Char ( toLower, isPunctuation, isAscii, isLetter, isDigit, ord )
|
2013-01-17 19:47:03 -08:00
|
|
|
import Control.Applicative ((<|>))
|
2013-03-05 22:09:42 -08:00
|
|
|
import Control.Monad.State
|
2010-12-19 10:13:55 -08:00
|
|
|
import Text.Pandoc.Pretty
|
2012-01-23 13:25:55 -08:00
|
|
|
import Text.Pandoc.Slides
|
2011-12-27 23:46:23 -08:00
|
|
|
import Text.Pandoc.Highlighting (highlight, styleToLaTeX,
|
2013-03-05 22:09:42 -08:00
|
|
|
formatLaTeXInline, formatLaTeXBlock,
|
|
|
|
toListingsLanguage)
|
2007-11-03 23:27:58 +00:00
|
|
|
|
2011-12-23 18:05:14 -08:00
|
|
|
data WriterState =
|
2011-12-30 16:14:35 -08: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
|
|
|
|
, stTable :: Bool -- true if document has a table
|
|
|
|
, stStrikeout :: Bool -- true if document has strikeout
|
|
|
|
, stUrl :: Bool -- true if document has visible URL link
|
|
|
|
, 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
|
|
|
|
, stHighlighting :: Bool -- true if document has highlighted code
|
|
|
|
, stIncremental :: Bool -- true if beamer lists should be displayed bit by bit
|
|
|
|
, stInternalLinks :: [String] -- list of internal link targets
|
2012-04-03 18:49:05 -07:00
|
|
|
, stUsesEuro :: Bool -- true if euro symbol used
|
2007-11-15 03:11:33 +00:00
|
|
|
}
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
-- | Convert Pandoc to LaTeX.
|
|
|
|
writeLaTeX :: WriterOptions -> Pandoc -> String
|
2011-12-23 18:05:14 -08:00
|
|
|
writeLaTeX options document =
|
|
|
|
evalState (pandocToLaTeX options document) $
|
2013-04-15 09:10:29 -07:00
|
|
|
WriterState { stInNote = False,
|
|
|
|
stOLLevel = 1, stOptions = options,
|
2012-09-16 22:24:55 -07:00
|
|
|
stVerbInNote = False,
|
2012-04-21 09:59:36 -07:00
|
|
|
stTable = False, stStrikeout = False,
|
2010-01-05 08:36:02 +00:00
|
|
|
stUrl = False, stGraphics = False,
|
2011-07-23 13:11:39 -07:00
|
|
|
stLHS = False, stBook = writerChapters options,
|
2011-12-29 13:24:05 -08:00
|
|
|
stCsquotes = False, stHighlighting = False,
|
2012-01-23 13:25:55 -08:00
|
|
|
stIncremental = writerIncremental options,
|
2012-04-03 18:49:05 -07:00
|
|
|
stInternalLinks = [], stUsesEuro = False }
|
2007-11-03 23:27:58 +00:00
|
|
|
|
2009-12-31 01:08:56 +00:00
|
|
|
pandocToLaTeX :: WriterOptions -> Pandoc -> State WriterState String
|
2013-05-10 22:53:35 -07:00
|
|
|
pandocToLaTeX options (Pandoc meta blocks) = do
|
2013-09-19 10:08:49 -07:00
|
|
|
-- Strip off final 'references' header if --natbib or --biblatex
|
|
|
|
let method = writerCiteMethod options
|
|
|
|
let blocks' = if method == Biblatex || method == Natbib
|
|
|
|
then case reverse blocks of
|
|
|
|
(Div (_,["references"],_) _):xs -> reverse xs
|
|
|
|
_ -> blocks
|
|
|
|
else blocks
|
2011-12-30 16:14:35 -08:00
|
|
|
-- see if there are internal links
|
|
|
|
let isInternalLink (Link _ ('#':xs,_)) = [xs]
|
|
|
|
isInternalLink _ = []
|
2013-09-19 10:08:49 -07:00
|
|
|
modify $ \s -> s{ stInternalLinks = query isInternalLink blocks' }
|
2010-01-03 08:47:54 +00:00
|
|
|
let template = writerTemplate options
|
2011-12-30 09:56:09 -08:00
|
|
|
-- set stBook depending on documentclass
|
|
|
|
let bookClasses = ["memoir","book","report","scrreprt","scrbook"]
|
|
|
|
case lookup "documentclass" (writerVariables options) of
|
|
|
|
Just x | x `elem` bookClasses -> modify $ \s -> s{stBook = True}
|
|
|
|
| otherwise -> return ()
|
|
|
|
Nothing | any (\x -> "\\documentclass" `isPrefixOf` x &&
|
|
|
|
(any (`isSuffixOf` x) bookClasses))
|
|
|
|
(lines template) -> modify $ \s -> s{stBook = True}
|
|
|
|
| otherwise -> return ()
|
2011-07-23 13:11:39 -07:00
|
|
|
-- check for \usepackage...{csquotes}; if present, we'll use
|
|
|
|
-- \enquote{...} for smart quotes:
|
|
|
|
when ("{csquotes}" `isInfixOf` template) $
|
|
|
|
modify $ \s -> s{stCsquotes = True}
|
2011-12-29 13:24:05 -08:00
|
|
|
let colwidth = if writerWrapText options
|
|
|
|
then Just $ writerColumns options
|
2010-12-19 10:13:55 -08:00
|
|
|
else Nothing
|
2013-07-01 20:47:26 -07:00
|
|
|
metadata <- metaToJSON options
|
2013-05-10 22:53:35 -07:00
|
|
|
(fmap (render colwidth) . blockListToLaTeX)
|
|
|
|
(fmap (render colwidth) . inlineListToLaTeX)
|
|
|
|
meta
|
2013-09-19 10:08:49 -07:00
|
|
|
let (blocks'', lastHeader) = if writerCiteMethod options == Citeproc then
|
|
|
|
(blocks', [])
|
|
|
|
else case last blocks' of
|
|
|
|
Header 1 _ il -> (init blocks', il)
|
|
|
|
_ -> (blocks', [])
|
|
|
|
blocks''' <- if writerBeamer options
|
|
|
|
then toSlides blocks''
|
|
|
|
else return blocks''
|
|
|
|
body <- mapM (elementToLaTeX options) $ hierarchicalize blocks'''
|
2013-05-10 22:53:35 -07:00
|
|
|
(biblioTitle :: String) <- liftM (render colwidth) $ inlineListToLaTeX lastHeader
|
2012-05-14 07:04:07 -07:00
|
|
|
let main = render colwidth $ vsep body
|
2009-12-31 01:18:14 +00:00
|
|
|
st <- get
|
2013-06-27 22:42:55 -07:00
|
|
|
let context = defField "toc" (writerTableOfContents options) $
|
|
|
|
defField "toc-depth" (show (writerTOCDepth options -
|
2013-05-10 22:53:35 -07:00
|
|
|
if writerChapters options
|
|
|
|
then 1
|
|
|
|
else 0)) $
|
2013-06-27 22:42:55 -07:00
|
|
|
defField "body" main $
|
|
|
|
defField "title-meta" (stringify $ docTitle meta) $
|
|
|
|
defField "author-meta" (intercalate "; " $ map stringify $ docAuthors meta) $
|
|
|
|
defField "documentclass" (if writerBeamer options
|
2013-05-10 22:53:35 -07:00
|
|
|
then ("beamer" :: String)
|
|
|
|
else if writerChapters options
|
|
|
|
then "book"
|
|
|
|
else "article") $
|
2013-06-27 22:42:55 -07:00
|
|
|
defField "verbatim-in-note" (stVerbInNote st) $
|
|
|
|
defField "tables" (stTable st) $
|
|
|
|
defField "strikeout" (stStrikeout st) $
|
|
|
|
defField "url" (stUrl st) $
|
|
|
|
defField "numbersections" (writerNumberSections options) $
|
|
|
|
defField "lhs" (stLHS st) $
|
|
|
|
defField "graphics" (stGraphics st) $
|
|
|
|
defField "book-class" (stBook st) $
|
|
|
|
defField "euro" (stUsesEuro st) $
|
|
|
|
defField "listings" (writerListings options || stLHS st) $
|
|
|
|
defField "beamer" (writerBeamer options) $
|
|
|
|
defField "mainlang" (maybe "" (reverse . takeWhile (/=',') . reverse)
|
2013-05-10 22:53:35 -07:00
|
|
|
(lookup "lang" $ writerVariables options)) $
|
|
|
|
(if stHighlighting st
|
2013-06-27 22:42:55 -07:00
|
|
|
then defField "highlighting-macros" (styleToLaTeX
|
2013-05-10 22:53:35 -07:00
|
|
|
$ writerHighlightStyle options )
|
|
|
|
else id) $
|
|
|
|
(case writerCiteMethod options of
|
2013-08-24 22:27:08 -07:00
|
|
|
Natbib -> defField "biblio-title" biblioTitle .
|
2013-06-27 22:42:55 -07:00
|
|
|
defField "natbib" True
|
2013-08-24 22:27:08 -07:00
|
|
|
Biblatex -> defField "biblio-title" biblioTitle .
|
2013-06-27 22:42:55 -07:00
|
|
|
defField "biblatex" True
|
2013-05-10 22:53:35 -07:00
|
|
|
_ -> id) $
|
2013-06-29 22:14:01 -07:00
|
|
|
metadata
|
2009-12-31 01:12:59 +00:00
|
|
|
return $ if writerStandalone options
|
2013-05-10 22:53:35 -07:00
|
|
|
then renderTemplate' template context
|
2009-12-31 01:12:59 +00:00
|
|
|
else main
|
2007-11-03 23:27:58 +00:00
|
|
|
|
2011-12-30 14:30:45 -08:00
|
|
|
-- | Convert Elements to LaTeX
|
|
|
|
elementToLaTeX :: WriterOptions -> Element -> State WriterState Doc
|
|
|
|
elementToLaTeX _ (Blk block) = blockToLaTeX block
|
2013-02-14 19:50:11 -08:00
|
|
|
elementToLaTeX opts (Sec level _ (id',classes,_) title' elements) = do
|
|
|
|
header' <- sectionHeader ("unnumbered" `elem` classes) id' level title'
|
2011-12-30 14:30:45 -08:00
|
|
|
innerContents <- mapM (elementToLaTeX opts) elements
|
2012-05-14 07:04:07 -07:00
|
|
|
return $ vsep (header' : innerContents)
|
2007-11-03 23:27:58 +00:00
|
|
|
|
2013-07-04 15:06:23 -07:00
|
|
|
data StringContext = TextString
|
|
|
|
| URLString
|
|
|
|
| CodeString
|
|
|
|
deriving (Eq)
|
|
|
|
|
2011-12-30 14:30:45 -08:00
|
|
|
-- escape things as needed for LaTeX
|
2013-07-04 15:06:23 -07:00
|
|
|
stringToLaTeX :: StringContext -> String -> State WriterState String
|
2012-05-11 22:58:49 -07:00
|
|
|
stringToLaTeX _ [] = return ""
|
2013-07-04 15:06:23 -07:00
|
|
|
stringToLaTeX ctx (x:xs) = do
|
2012-05-11 22:58:49 -07:00
|
|
|
opts <- gets stOptions
|
2013-07-04 15:06:23 -07:00
|
|
|
rest <- stringToLaTeX ctx xs
|
|
|
|
let ligatures = writerTeXLigatures opts && not (ctx == CodeString)
|
|
|
|
let isUrl = ctx == URLString
|
2012-04-03 18:49:05 -07:00
|
|
|
when (x == '€') $
|
|
|
|
modify $ \st -> st{ stUsesEuro = True }
|
|
|
|
return $
|
|
|
|
case x of
|
|
|
|
'€' -> "\\euro{}" ++ rest
|
2012-02-06 13:48:59 -08:00
|
|
|
'{' -> "\\{" ++ rest
|
|
|
|
'}' -> "\\}" ++ rest
|
|
|
|
'$' -> "\\$" ++ rest
|
|
|
|
'%' -> "\\%" ++ rest
|
|
|
|
'&' -> "\\&" ++ rest
|
2012-09-15 20:42:24 -07:00
|
|
|
'_' | not isUrl -> "\\_" ++ rest
|
2012-02-06 13:48:59 -08:00
|
|
|
'#' -> "\\#" ++ rest
|
|
|
|
'-' -> case xs of -- prevent adjacent hyphens from forming ligatures
|
|
|
|
('-':_) -> "-{}" ++ rest
|
|
|
|
_ -> '-' : rest
|
2012-03-03 06:33:24 -08:00
|
|
|
'~' | not isUrl -> "\\textasciitilde{}" ++ rest
|
2012-02-06 13:48:59 -08:00
|
|
|
'^' -> "\\^{}" ++ rest
|
2013-07-25 20:29:42 -07:00
|
|
|
'\\'| isUrl -> '/' : rest -- NB. / works as path sep even on Windows
|
|
|
|
| otherwise -> "\\textbackslash{}" ++ rest
|
2012-02-06 13:48:59 -08:00
|
|
|
'|' -> "\\textbar{}" ++ rest
|
|
|
|
'<' -> "\\textless{}" ++ rest
|
|
|
|
'>' -> "\\textgreater{}" ++ rest
|
|
|
|
'[' -> "{[}" ++ rest -- to avoid interpretation as
|
|
|
|
']' -> "{]}" ++ rest -- optional arguments
|
|
|
|
'\160' -> "~" ++ rest
|
|
|
|
'\x2026' -> "\\ldots{}" ++ rest
|
2012-05-11 22:58:49 -07:00
|
|
|
'\x2018' | ligatures -> "`" ++ rest
|
|
|
|
'\x2019' | ligatures -> "'" ++ rest
|
|
|
|
'\x201C' | ligatures -> "``" ++ rest
|
|
|
|
'\x201D' | ligatures -> "''" ++ rest
|
|
|
|
'\x2014' | ligatures -> "---" ++ rest
|
|
|
|
'\x2013' | ligatures -> "--" ++ rest
|
2012-02-06 13:48:59 -08:00
|
|
|
_ -> x : rest
|
2007-11-03 23:27:58 +00:00
|
|
|
|
2013-10-17 22:06:39 -07:00
|
|
|
toLabel :: String -> String
|
|
|
|
toLabel [] = ""
|
|
|
|
toLabel (x:xs)
|
|
|
|
| (isLetter x || isDigit x) && isAscii x = x:toLabel xs
|
|
|
|
| elem x "-+=:;." = x:toLabel xs
|
|
|
|
| otherwise = "ux" ++ printf "%x" (ord x) ++ toLabel xs
|
|
|
|
|
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
|
|
|
|
|
2011-12-29 13:24:05 -08:00
|
|
|
toSlides :: [Block] -> State WriterState [Block]
|
2012-01-23 23:02:18 -08:00
|
|
|
toSlides bs = do
|
2012-01-25 17:50:03 -08:00
|
|
|
opts <- gets stOptions
|
|
|
|
let slideLevel = maybe (getSlideLevel bs) id $ writerSlideLevel opts
|
2012-01-23 23:02:18 -08:00
|
|
|
let bs' = prepSlides slideLevel bs
|
|
|
|
concat `fmap` (mapM (elementToBeamer slideLevel) $ hierarchicalize bs')
|
|
|
|
|
|
|
|
elementToBeamer :: Int -> Element -> State WriterState [Block]
|
|
|
|
elementToBeamer _slideLevel (Blk b) = return [b]
|
2013-07-26 12:40:56 -07:00
|
|
|
elementToBeamer slideLevel (Sec lvl _num (ident,classes,kvs) tit elts)
|
2012-01-23 23:02:18 -08:00
|
|
|
| lvl > slideLevel = do
|
|
|
|
bs <- concat `fmap` mapM (elementToBeamer slideLevel) elts
|
|
|
|
return $ Para ( RawInline "latex" "\\begin{block}{"
|
|
|
|
: tit ++ [RawInline "latex" "}"] )
|
|
|
|
: bs ++ [RawBlock "latex" "\\end{block}"]
|
|
|
|
| lvl < slideLevel = do
|
|
|
|
bs <- concat `fmap` mapM (elementToBeamer slideLevel) elts
|
2013-07-26 12:40:56 -07:00
|
|
|
return $ (Header lvl (ident,classes,kvs) tit) : bs
|
2012-01-23 23:02:18 -08:00
|
|
|
| otherwise = do -- lvl == slideLevel
|
|
|
|
-- note: [fragile] is required or verbatim breaks
|
|
|
|
let hasCodeBlock (CodeBlock _ _) = [True]
|
|
|
|
hasCodeBlock _ = []
|
|
|
|
let hasCode (Code _ _) = [True]
|
|
|
|
hasCode _ = []
|
2012-11-04 11:09:15 -08:00
|
|
|
opts <- gets stOptions
|
2013-08-10 18:13:38 -07:00
|
|
|
let fragile = not $ null $ query hasCodeBlock elts ++
|
2012-11-04 11:09:15 -08:00
|
|
|
if writerListings opts
|
2013-08-10 18:13:38 -07:00
|
|
|
then query hasCode elts
|
2012-11-04 11:09:15 -08:00
|
|
|
else []
|
2013-07-26 12:40:56 -07:00
|
|
|
let allowframebreaks = "allowframebreaks" `elem` classes
|
|
|
|
let optionslist = ["fragile" | fragile] ++
|
|
|
|
["allowframebreaks" | allowframebreaks]
|
|
|
|
let options = if null optionslist
|
|
|
|
then ""
|
|
|
|
else "[" ++ intercalate "," optionslist ++ "]"
|
|
|
|
let slideStart = Para $ RawInline "latex" ("\\begin{frame}" ++ options) :
|
2012-06-25 14:52:09 -07:00
|
|
|
if tit == [Str "\0"] -- marker for hrule
|
|
|
|
then []
|
2013-07-26 12:40:56 -07:00
|
|
|
else (RawInline "latex" "{") : tit ++ [RawInline "latex" "}"]
|
2012-01-23 23:02:18 -08:00
|
|
|
let slideEnd = RawBlock "latex" "\\end{frame}"
|
|
|
|
-- now carve up slide into blocks if there are sections inside
|
|
|
|
bs <- concat `fmap` mapM (elementToBeamer slideLevel) elts
|
|
|
|
return $ slideStart : bs ++ [slideEnd]
|
2011-12-29 13:24:05 -08:00
|
|
|
|
|
|
|
isListBlock :: Block -> Bool
|
|
|
|
isListBlock (BulletList _) = True
|
|
|
|
isListBlock (OrderedList _ _) = True
|
|
|
|
isListBlock (DefinitionList _) = True
|
|
|
|
isListBlock _ = False
|
|
|
|
|
2013-01-15 23:02:08 -08:00
|
|
|
isLineBreakOrSpace :: Inline -> Bool
|
|
|
|
isLineBreakOrSpace LineBreak = True
|
|
|
|
isLineBreakOrSpace Space = True
|
|
|
|
isLineBreakOrSpace _ = False
|
|
|
|
|
2007-11-03 23:27:58 +00:00
|
|
|
-- | Convert Pandoc block element to LaTeX.
|
|
|
|
blockToLaTeX :: Block -- ^ Block to convert
|
|
|
|
-> State WriterState Doc
|
|
|
|
blockToLaTeX Null = return empty
|
2013-10-13 15:36:19 -07:00
|
|
|
blockToLaTeX (Div (_,classes,_) bs) = do
|
|
|
|
beamer <- writerBeamer `fmap` gets stOptions
|
|
|
|
contents <- blockListToLaTeX bs
|
|
|
|
if beamer && "notes" `elem` classes -- speaker notes
|
|
|
|
then return $ "\\note" <> braces contents
|
|
|
|
else return contents
|
2013-01-15 23:02:08 -08:00
|
|
|
blockToLaTeX (Plain lst) =
|
|
|
|
inlineListToLaTeX $ dropWhile isLineBreakOrSpace lst
|
2013-01-15 08:45:46 -08:00
|
|
|
-- title beginning with fig: indicates that the image is a figure
|
|
|
|
blockToLaTeX (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
|
2012-08-04 11:34:01 -07:00
|
|
|
capt <- if null txt
|
|
|
|
then return empty
|
|
|
|
else (\c -> "\\caption" <> braces c) `fmap` inlineListToLaTeX 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 $$
|
2012-08-04 11:34:01 -07:00
|
|
|
capt $$ "\\end{figure}"
|
2013-03-24 21:02:06 -07:00
|
|
|
-- . . . indicates pause in beamer slides
|
|
|
|
blockToLaTeX (Para [Str ".",Space,Str ".",Space,Str "."]) = do
|
|
|
|
beamer <- writerBeamer `fmap` gets stOptions
|
|
|
|
if beamer
|
|
|
|
then blockToLaTeX (RawBlock "latex" "\\pause")
|
|
|
|
else inlineListToLaTeX [Str ".",Space,Str ".",Space,Str "."]
|
2013-01-15 23:02:08 -08:00
|
|
|
blockToLaTeX (Para lst) =
|
|
|
|
inlineListToLaTeX $ dropWhile isLineBreakOrSpace lst
|
2007-11-03 23:27:58 +00:00
|
|
|
blockToLaTeX (BlockQuote lst) = do
|
2011-12-29 13:24:05 -08:00
|
|
|
beamer <- writerBeamer `fmap` gets stOptions
|
|
|
|
case lst of
|
|
|
|
[b] | beamer && isListBlock b -> do
|
|
|
|
oldIncremental <- gets stIncremental
|
2012-06-03 09:14:09 -07:00
|
|
|
modify $ \s -> s{ stIncremental = not oldIncremental }
|
2011-12-29 13:24:05 -08:00
|
|
|
result <- blockToLaTeX b
|
|
|
|
modify $ \s -> s{ stIncremental = oldIncremental }
|
|
|
|
return result
|
|
|
|
_ -> do
|
|
|
|
contents <- blockListToLaTeX lst
|
2012-05-14 07:04:07 -07:00
|
|
|
return $ "\\begin{quote}" $$ contents $$ "\\end{quote}"
|
2013-08-22 20:15:36 +02:00
|
|
|
blockToLaTeX (CodeBlock (identifier,classes,keyvalAttr) str) = do
|
2011-12-23 18:05:14 -08:00
|
|
|
opts <- gets stOptions
|
|
|
|
case () of
|
2012-08-08 23:18:19 -07:00
|
|
|
_ | isEnabled Ext_literate_haskell opts && "haskell" `elem` classes &&
|
2011-12-23 18:05:14 -08:00
|
|
|
"literate" `elem` classes -> lhsCodeBlock
|
|
|
|
| writerListings opts -> listingsCodeBlock
|
|
|
|
| writerHighlight opts && not (null classes) -> highlightedCodeBlock
|
|
|
|
| otherwise -> rawCodeBlock
|
2013-10-17 22:06:39 -07:00
|
|
|
where ref = text $ toLabel identifier
|
2013-10-17 13:23:38 -07:00
|
|
|
linkAnchor = if null identifier
|
|
|
|
then empty
|
|
|
|
else "\\hyperdef{}" <> braces ref <>
|
|
|
|
braces ("\\label" <> braces ref)
|
|
|
|
lhsCodeBlock = do
|
2011-12-23 18:05:14 -08:00
|
|
|
modify $ \s -> s{ stLHS = True }
|
2013-10-17 13:23:38 -07:00
|
|
|
return $ flush (linkAnchor $$ "\\begin{code}" $$ text str $$
|
|
|
|
"\\end{code}") $$ cr
|
2011-12-23 18:05:14 -08:00
|
|
|
rawCodeBlock = do
|
|
|
|
st <- get
|
|
|
|
env <- if stInNote st
|
|
|
|
then modify (\s -> s{ stVerbInNote = True }) >>
|
|
|
|
return "Verbatim"
|
|
|
|
else return "verbatim"
|
2013-10-17 13:23:38 -07:00
|
|
|
return $ flush (linkAnchor $$ text ("\\begin{" ++ env ++ "}") $$
|
|
|
|
text str $$ text ("\\end{" ++ env ++ "}")) <> cr
|
2011-12-23 18:05:14 -08:00
|
|
|
listingsCodeBlock = do
|
|
|
|
st <- get
|
|
|
|
let params = if writerListings (stOptions st)
|
2013-01-17 19:47:03 -08:00
|
|
|
then (case getListingsLanguage classes of
|
|
|
|
Just l -> [ "language=" ++ l ]
|
|
|
|
Nothing -> []) ++
|
2013-03-04 09:31:31 -08:00
|
|
|
[ "numbers=left" | "numberLines" `elem` classes
|
|
|
|
|| "number" `elem` classes
|
|
|
|
|| "number-lines" `elem` classes ] ++
|
|
|
|
[ (if key == "startFrom"
|
|
|
|
then "firstnumber"
|
|
|
|
else key) ++ "=" ++ attr |
|
2013-08-22 20:15:36 +02:00
|
|
|
(key,attr) <- keyvalAttr ] ++
|
|
|
|
(if identifier == ""
|
|
|
|
then []
|
2013-10-17 22:06:39 -07:00
|
|
|
else [ "label=" ++ toLabel identifier ])
|
2013-08-22 20:15:36 +02:00
|
|
|
|
2011-12-23 18:05:14 -08:00
|
|
|
else []
|
|
|
|
printParams
|
|
|
|
| null params = empty
|
2013-03-04 09:31:31 -08:00
|
|
|
| otherwise = brackets $ hcat (intersperse ", " (map text params))
|
2011-12-23 18:05:14 -08:00
|
|
|
return $ flush ("\\begin{lstlisting}" <> printParams $$ text str $$
|
|
|
|
"\\end{lstlisting}") $$ cr
|
|
|
|
highlightedCodeBlock =
|
2011-12-26 22:49:50 -08:00
|
|
|
case highlight formatLaTeXBlock ("",classes,keyvalAttr) str of
|
2011-12-23 18:05:14 -08:00
|
|
|
Nothing -> rawCodeBlock
|
|
|
|
Just h -> modify (\st -> st{ stHighlighting = True }) >>
|
2013-10-17 13:23:38 -07:00
|
|
|
return (flush $ linkAnchor $$ text h)
|
2013-08-10 17:23:51 -07:00
|
|
|
blockToLaTeX (RawBlock f x)
|
|
|
|
| f == Format "latex" || f == Format "tex"
|
|
|
|
= return $ text x
|
|
|
|
| otherwise = return empty
|
2013-02-16 17:44:58 -08:00
|
|
|
blockToLaTeX (BulletList []) = return empty -- otherwise latex error
|
2007-11-03 23:27:58 +00:00
|
|
|
blockToLaTeX (BulletList lst) = do
|
2011-12-29 13:24:05 -08:00
|
|
|
incremental <- gets stIncremental
|
|
|
|
let inc = if incremental then "[<+->]" else ""
|
2007-11-03 23:27:58 +00:00
|
|
|
items <- mapM listItemToLaTeX lst
|
2013-01-07 20:12:13 -08:00
|
|
|
let spacing = if isTightList lst
|
|
|
|
then text "\\itemsep1pt\\parskip0pt\\parsep0pt"
|
|
|
|
else empty
|
|
|
|
return $ text ("\\begin{itemize}" ++ inc) $$ spacing $$ vcat items $$
|
2012-05-14 07:04:07 -07:00
|
|
|
"\\end{itemize}"
|
2013-02-16 17:44:58 -08:00
|
|
|
blockToLaTeX (OrderedList _ []) = return empty -- otherwise latex error
|
2007-11-03 23:27:58 +00:00
|
|
|
blockToLaTeX (OrderedList (start, numstyle, numdelim) lst) = do
|
|
|
|
st <- get
|
2011-12-29 13:24:05 -08:00
|
|
|
let inc = if stIncremental st then "[<+->]" else ""
|
2007-11-03 23:27:58 +00:00
|
|
|
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})
|
2012-09-16 22:24:55 -07:00
|
|
|
let tostyle x = case numstyle of
|
2013-01-09 15:54:39 -08:00
|
|
|
Decimal -> "\\arabic" <> braces x
|
|
|
|
UpperRoman -> "\\Roman" <> braces x
|
|
|
|
LowerRoman -> "\\roman" <> braces x
|
|
|
|
UpperAlpha -> "\\Alph" <> braces x
|
|
|
|
LowerAlpha -> "\\alph" <> braces x
|
|
|
|
Example -> "\\arabic" <> braces x
|
|
|
|
DefaultStyle -> "\\arabic" <> braces x
|
2012-09-16 22:24:55 -07:00
|
|
|
let todelim x = case numdelim of
|
|
|
|
OneParen -> x <> ")"
|
|
|
|
TwoParens -> parens x
|
|
|
|
Period -> x <> "."
|
|
|
|
_ -> x <> "."
|
|
|
|
let enum = text $ "enum" ++ map toLower (toRomanNumeral oldlevel)
|
|
|
|
let stylecommand = if numstyle == DefaultStyle && numdelim == DefaultDelim
|
|
|
|
then empty
|
|
|
|
else "\\def" <> "\\label" <> enum <>
|
|
|
|
braces (todelim $ tostyle enum)
|
|
|
|
let resetcounter = if start == 1 || oldlevel > 4
|
|
|
|
then empty
|
|
|
|
else "\\setcounter" <> braces enum <>
|
|
|
|
braces (text $ show $ start - 1)
|
2013-01-07 20:12:13 -08:00
|
|
|
let spacing = if isTightList lst
|
|
|
|
then text "\\itemsep1pt\\parskip0pt\\parsep0pt"
|
|
|
|
else empty
|
2012-09-16 22:24:55 -07:00
|
|
|
return $ text ("\\begin{enumerate}" ++ inc)
|
|
|
|
$$ stylecommand
|
|
|
|
$$ resetcounter
|
2013-01-07 20:12:13 -08:00
|
|
|
$$ spacing
|
2012-09-16 22:24:55 -07:00
|
|
|
$$ vcat items
|
|
|
|
$$ "\\end{enumerate}"
|
2013-02-16 17:44:58 -08:00
|
|
|
blockToLaTeX (DefinitionList []) = return empty
|
2007-11-03 23:27:58 +00:00
|
|
|
blockToLaTeX (DefinitionList lst) = do
|
2011-12-29 13:24:05 -08:00
|
|
|
incremental <- gets stIncremental
|
|
|
|
let inc = if incremental then "[<+->]" else ""
|
2007-11-03 23:27:58 +00:00
|
|
|
items <- mapM defListItemToLaTeX lst
|
2013-01-07 20:12:13 -08:00
|
|
|
let spacing = if and $ map isTightList (map snd lst)
|
|
|
|
then text "\\itemsep1pt\\parskip0pt\\parsep0pt"
|
|
|
|
else empty
|
|
|
|
return $ text ("\\begin{description}" ++ inc) $$ spacing $$ vcat items $$
|
2012-05-14 07:04:07 -07:00
|
|
|
"\\end{description}"
|
2010-12-19 10:13:55 -08:00
|
|
|
blockToLaTeX HorizontalRule = return $
|
2012-05-14 07:04:07 -07:00
|
|
|
"\\begin{center}\\rule{3in}{0.4pt}\\end{center}"
|
2013-02-14 19:50:11 -08:00
|
|
|
blockToLaTeX (Header level (id',classes,_) lst) =
|
|
|
|
sectionHeader ("unnumbered" `elem` classes) id' level lst
|
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
|
2012-09-15 20:38:19 -07:00
|
|
|
else ($$ "\\hline\\noalign{\\medskip}") `fmap`
|
2012-09-15 17:48:43 -04:00
|
|
|
(tableRowToLaTeX True aligns widths) heads
|
2011-07-22 12:19:34 -07:00
|
|
|
captionText <- inlineListToLaTeX caption
|
2011-07-10 09:13:10 -07:00
|
|
|
let capt = if isEmpty captionText
|
|
|
|
then empty
|
2012-09-15 17:48:43 -04:00
|
|
|
else text "\\noalign{\\medskip}"
|
|
|
|
$$ text "\\caption" <> braces captionText
|
2011-07-10 09:13:10 -07:00
|
|
|
rows' <- mapM (tableRowToLaTeX False aligns widths) rows
|
|
|
|
let colDescriptors = text $ concat $ map toColDescriptor aligns
|
2013-04-15 09:10:29 -07:00
|
|
|
modify $ \s -> s{ stTable = True }
|
2013-01-28 10:21:18 -08:00
|
|
|
return $ "\\begin{longtable}[c]" <>
|
|
|
|
braces ("@{}" <> colDescriptors <> "@{}")
|
|
|
|
-- the @{} removes extra space at beginning and end
|
2012-09-15 17:48:43 -04:00
|
|
|
$$ "\\hline\\noalign{\\medskip}"
|
|
|
|
$$ headers
|
|
|
|
$$ vcat rows'
|
|
|
|
$$ "\\hline"
|
|
|
|
$$ capt
|
|
|
|
$$ "\\end{longtable}"
|
2007-11-03 23:27:58 +00:00
|
|
|
|
2011-07-10 09:13:10 -07:00
|
|
|
toColDescriptor :: Alignment -> String
|
|
|
|
toColDescriptor align =
|
2009-11-28 03:22:33 +00:00
|
|
|
case align of
|
|
|
|
AlignLeft -> "l"
|
|
|
|
AlignRight -> "r"
|
|
|
|
AlignCenter -> "c"
|
|
|
|
AlignDefault -> "l"
|
|
|
|
|
2008-07-13 16:53:06 +00:00
|
|
|
blockListToLaTeX :: [Block] -> State WriterState Doc
|
2012-05-14 07:04:07 -07:00
|
|
|
blockListToLaTeX lst = vsep `fmap` mapM blockToLaTeX lst
|
2007-11-03 23:27:58 +00:00
|
|
|
|
2011-07-10 09:13:10 -07:00
|
|
|
tableRowToLaTeX :: Bool
|
|
|
|
-> [Alignment]
|
|
|
|
-> [Double]
|
|
|
|
-> [[Block]]
|
|
|
|
-> State WriterState Doc
|
|
|
|
tableRowToLaTeX header aligns widths cols = do
|
2011-01-14 14:45:04 -08:00
|
|
|
renderedCells <- mapM blockListToLaTeX cols
|
2011-07-10 09:13:10 -07:00
|
|
|
let valign = text $ if header then "[b]" else "[t]"
|
|
|
|
let halign x = case x of
|
|
|
|
AlignLeft -> "\\raggedright"
|
|
|
|
AlignRight -> "\\raggedleft"
|
|
|
|
AlignCenter -> "\\centering"
|
|
|
|
AlignDefault -> "\\raggedright"
|
2013-08-19 16:03:22 -07:00
|
|
|
-- scale factor compensates for extra space between columns
|
|
|
|
-- so the whole table isn't larger than columnwidth
|
|
|
|
let scaleFactor = 0.97 ** fromIntegral (length aligns)
|
2011-07-10 09:13:10 -07:00
|
|
|
let toCell 0 _ c = c
|
2013-01-05 19:11:06 -08:00
|
|
|
toCell w a c = "\\begin{minipage}" <> valign <>
|
2013-08-19 16:03:22 -07:00
|
|
|
braces (text (printf "%.2f\\columnwidth"
|
|
|
|
(w * scaleFactor))) <>
|
2013-01-05 19:11:06 -08:00
|
|
|
(halign a <> cr <> c <> cr) <> "\\end{minipage}"
|
2011-07-10 09:13:10 -07:00
|
|
|
let cells = zipWith3 toCell widths aligns renderedCells
|
2012-09-15 17:48:43 -04:00
|
|
|
return $ hsep (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
|
2011-07-22 12:19:34 -07:00
|
|
|
term' <- inlineListToLaTeX 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
|
|
|
|
2011-12-30 14:30:45 -08:00
|
|
|
-- | Craft the section header, inserting the secton reference, if supplied.
|
2013-02-14 19:50:11 -08:00
|
|
|
sectionHeader :: Bool -- True for unnumbered
|
|
|
|
-> [Char]
|
2011-12-30 14:30:45 -08:00
|
|
|
-> Int
|
|
|
|
-> [Inline]
|
|
|
|
-> State WriterState Doc
|
2013-02-14 19:50:11 -08:00
|
|
|
sectionHeader unnumbered ref level lst = do
|
2011-12-30 14:30:45 -08:00
|
|
|
txt <- inlineListToLaTeX lst
|
|
|
|
let noNote (Note _) = Str ""
|
|
|
|
noNote x = x
|
2013-08-10 18:45:00 -07:00
|
|
|
let lstNoNotes = walk noNote lst
|
2013-08-16 13:02:55 -07:00
|
|
|
txtNoNotes <- inlineListToLaTeX lstNoNotes
|
2013-02-14 19:50:11 -08:00
|
|
|
let star = if unnumbered then text "*" else empty
|
2013-08-16 13:02:55 -07:00
|
|
|
-- footnotes in sections don't work (except for starred variants)
|
|
|
|
-- unless you specify an optional argument:
|
|
|
|
-- \section[mysec]{mysec\footnote{blah}}
|
|
|
|
optional <- if unnumbered || lstNoNotes == lst
|
2011-12-30 14:30:45 -08:00
|
|
|
then return empty
|
|
|
|
else do
|
2013-08-16 13:02:55 -07:00
|
|
|
return $ brackets txtNoNotes
|
2013-02-15 19:23:51 -08:00
|
|
|
let stuffing = star <> optional <> braces txt
|
2012-01-25 10:47:22 -08:00
|
|
|
book <- gets stBook
|
|
|
|
opts <- gets stOptions
|
|
|
|
let level' = if book || writerChapters opts then level - 1 else level
|
2011-12-30 16:14:35 -08:00
|
|
|
internalLinks <- gets stInternalLinks
|
2013-06-02 14:37:15 -07:00
|
|
|
let refLabel x = (if ref `elem` internalLinks
|
|
|
|
then text "\\hyperdef"
|
2011-12-30 16:14:35 -08:00
|
|
|
<> braces empty
|
2013-10-17 22:06:39 -07:00
|
|
|
<> braces (text $ toLabel ref)
|
2013-06-02 14:37:15 -07:00
|
|
|
<> braces x
|
|
|
|
else x)
|
|
|
|
let headerWith x y r = refLabel $ text x <> y <>
|
|
|
|
if null r
|
|
|
|
then empty
|
2013-10-17 22:06:39 -07:00
|
|
|
else text "\\label" <> braces (text $ toLabel r)
|
2013-02-15 19:23:51 -08:00
|
|
|
let sectionType = case level' of
|
|
|
|
0 | writerBeamer opts -> "part"
|
|
|
|
| otherwise -> "chapter"
|
|
|
|
1 -> "section"
|
|
|
|
2 -> "subsection"
|
|
|
|
3 -> "subsubsection"
|
|
|
|
4 -> "paragraph"
|
|
|
|
5 -> "subparagraph"
|
|
|
|
_ -> ""
|
|
|
|
return $ if level' > 5
|
|
|
|
then txt
|
2013-06-02 14:37:15 -07:00
|
|
|
else headerWith ('\\':sectionType) stuffing ref
|
2013-02-15 19:23:51 -08:00
|
|
|
$$ if unnumbered
|
|
|
|
then "\\addcontentsline{toc}" <>
|
|
|
|
braces (text sectionType) <>
|
2013-08-16 13:02:55 -07:00
|
|
|
braces txtNoNotes
|
2013-02-15 19:23:51 -08:00
|
|
|
else empty
|
2011-12-30 14:30:45 -08:00
|
|
|
|
2007-11-03 23:27:58 +00:00
|
|
|
-- | Convert list of inline elements to LaTeX.
|
|
|
|
inlineListToLaTeX :: [Inline] -- ^ Inlines to convert
|
|
|
|
-> State WriterState Doc
|
2013-01-11 20:40:00 -08:00
|
|
|
inlineListToLaTeX lst =
|
|
|
|
mapM inlineToLaTeX (fixLineInitialSpaces lst)
|
|
|
|
>>= return . hcat
|
|
|
|
-- nonbreaking spaces (~) in LaTeX don't work after line breaks,
|
|
|
|
-- so we turn nbsps after hard breaks to \hspace commands.
|
|
|
|
-- this is mostly used in verse.
|
|
|
|
where fixLineInitialSpaces [] = []
|
|
|
|
fixLineInitialSpaces (LineBreak : Str s@('\160':_) : xs) =
|
|
|
|
LineBreak : fixNbsps s ++ fixLineInitialSpaces xs
|
|
|
|
fixLineInitialSpaces (x:xs) = x : fixLineInitialSpaces xs
|
|
|
|
fixNbsps s = let (ys,zs) = span (=='\160') s
|
|
|
|
in replicate (length ys) hspace ++ [Str zs]
|
2013-01-11 20:44:39 -08:00
|
|
|
hspace = RawInline "latex" "\\hspace*{0.333em}"
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
isQuoted :: Inline -> Bool
|
|
|
|
isQuoted (Quoted _ _) = True
|
|
|
|
isQuoted _ = False
|
|
|
|
|
|
|
|
-- | Convert inline element to LaTeX
|
|
|
|
inlineToLaTeX :: Inline -- ^ Inline to convert
|
|
|
|
-> State WriterState Doc
|
2013-08-08 23:14:12 -07:00
|
|
|
inlineToLaTeX (Span _ ils) = inlineListToLaTeX ils >>= return . braces
|
2007-11-03 23:27:58 +00:00
|
|
|
inlineToLaTeX (Emph lst) =
|
2011-07-22 12:19:34 -07:00
|
|
|
inlineListToLaTeX lst >>= return . inCmd "emph"
|
2011-12-23 18:05:14 -08:00
|
|
|
inlineToLaTeX (Strong lst) =
|
|
|
|
inlineListToLaTeX lst >>= return . inCmd "textbf"
|
2007-11-03 23:27:58 +00:00
|
|
|
inlineToLaTeX (Strikeout lst) = do
|
2011-07-22 12:19:34 -07:00
|
|
|
contents <- inlineListToLaTeX 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) =
|
2011-07-22 12:19:34 -07:00
|
|
|
inlineListToLaTeX lst >>= return . inCmd "textsuperscript"
|
2007-11-03 23:27:58 +00:00
|
|
|
inlineToLaTeX (Subscript lst) = do
|
2012-04-21 09:59:36 -07:00
|
|
|
inlineListToLaTeX lst >>= return . inCmd "textsubscript"
|
2008-07-15 23:26:06 +00:00
|
|
|
inlineToLaTeX (SmallCaps lst) =
|
2011-07-22 12:19:34 -07:00
|
|
|
inlineListToLaTeX 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-12-23 18:37:52 -08:00
|
|
|
inlineToLaTeX (Code (_,classes,_) str) = do
|
|
|
|
opts <- gets stOptions
|
|
|
|
case () of
|
|
|
|
_ | writerListings opts -> listingsCode
|
|
|
|
| writerHighlight opts && not (null classes) -> highlightCode
|
|
|
|
| otherwise -> rawCode
|
|
|
|
where listingsCode = do
|
|
|
|
inNote <- gets stInNote
|
|
|
|
when inNote $ modify $ \s -> s{ stVerbInNote = True }
|
|
|
|
let chr = ((enumFromTo '!' '~') \\ str) !! 0
|
|
|
|
return $ text $ "\\lstinline" ++ [chr] ++ str ++ [chr]
|
|
|
|
highlightCode = do
|
2011-12-26 22:49:50 -08:00
|
|
|
case highlight formatLaTeXInline ("",classes,[]) str of
|
2011-12-23 18:37:52 -08:00
|
|
|
Nothing -> rawCode
|
|
|
|
Just h -> modify (\st -> st{ stHighlighting = True }) >>
|
|
|
|
return (text h)
|
2012-04-03 18:49:05 -07:00
|
|
|
rawCode = liftM (text . (\s -> "\\texttt{" ++ s ++ "}"))
|
2013-07-04 15:06:23 -07:00
|
|
|
$ stringToLaTeX CodeString str
|
2012-05-11 22:58:49 -07:00
|
|
|
inlineToLaTeX (Quoted qt lst) = do
|
2007-11-03 23:27:58 +00:00
|
|
|
contents <- inlineListToLaTeX lst
|
2011-07-23 13:11:39 -07:00
|
|
|
csquotes <- liftM stCsquotes get
|
2012-05-11 22:58:49 -07:00
|
|
|
opts <- gets stOptions
|
2011-07-23 13:11:39 -07:00
|
|
|
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
|
2012-05-11 22:58:49 -07:00
|
|
|
let inner = s1 <> contents <> s2
|
|
|
|
return $ case qt of
|
|
|
|
DoubleQuote ->
|
|
|
|
if writerTeXLigatures opts
|
|
|
|
then text "``" <> inner <> text "''"
|
|
|
|
else char '\x201C' <> inner <> char '\x201D'
|
|
|
|
SingleQuote ->
|
|
|
|
if writerTeXLigatures opts
|
|
|
|
then char '`' <> inner <> char '\''
|
|
|
|
else char '\x2018' <> inner <> char '\x2019'
|
2013-07-04 15:06:23 -07:00
|
|
|
inlineToLaTeX (Str str) = liftM text $ stringToLaTeX TextString str
|
2013-01-12 10:21:19 -08:00
|
|
|
inlineToLaTeX (Math InlineMath str) =
|
2013-06-26 20:54:31 -07:00
|
|
|
return $ char '$' <> text str <> char '$'
|
2013-01-12 10:21:19 -08:00
|
|
|
inlineToLaTeX (Math DisplayMath str) =
|
2013-06-26 20:54:31 -07:00
|
|
|
return $ "\\[" <> text str <> "\\]"
|
2013-08-10 17:23:51 -07:00
|
|
|
inlineToLaTeX (RawInline f str)
|
|
|
|
| f == Format "latex" || f == Format "tex"
|
|
|
|
= return $ text str
|
|
|
|
| otherwise = 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
|
2012-04-21 09:41:05 -07:00
|
|
|
inlineToLaTeX (Link txt ('#':ident, _)) = do
|
|
|
|
contents <- inlineListToLaTeX txt
|
2013-07-04 15:06:23 -07:00
|
|
|
ident' <- stringToLaTeX URLString ident
|
2013-10-17 22:06:39 -07:00
|
|
|
return $ text "\\hyperref" <> brackets (text $ toLabel ident') <>
|
|
|
|
braces contents
|
2010-01-05 08:36:02 +00:00
|
|
|
inlineToLaTeX (Link txt (src, _)) =
|
2007-11-03 23:27:58 +00:00
|
|
|
case txt of
|
2013-01-06 20:51:51 -08:00
|
|
|
[Str x] | x == src -> -- autolink
|
2009-12-31 01:18:14 +00:00
|
|
|
do modify $ \s -> s{ stUrl = True }
|
2013-07-04 15:06:23 -07:00
|
|
|
src' <- stringToLaTeX URLString x
|
2012-09-16 11:20:53 -07:00
|
|
|
return $ text $ "\\url{" ++ src' ++ "}"
|
2011-07-22 12:19:34 -07:00
|
|
|
_ -> do contents <- inlineListToLaTeX txt
|
2013-07-04 15:06:23 -07:00
|
|
|
src' <- stringToLaTeX URLString src
|
2012-04-03 18:49:05 -07:00
|
|
|
return $ text ("\\href{" ++ src' ++ "}{") <>
|
2011-01-14 18:59:50 -08:00
|
|
|
contents <> char '}'
|
2009-12-31 01:18:14 +00:00
|
|
|
inlineToLaTeX (Image _ (source, _)) = do
|
|
|
|
modify $ \s -> s{ stGraphics = True }
|
2013-10-16 09:48:11 -07:00
|
|
|
let source' = if isURI source
|
2011-07-16 14:04:19 -07:00
|
|
|
then source
|
|
|
|
else unEscapeString source
|
2013-07-25 20:29:42 -07:00
|
|
|
source'' <- stringToLaTeX URLString source'
|
|
|
|
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})
|
2012-06-01 10:50:22 -07:00
|
|
|
let optnl = case reverse contents of
|
|
|
|
(CodeBlock _ _ : _) -> cr
|
|
|
|
_ -> empty
|
2013-04-15 09:10:29 -07:00
|
|
|
return $ "\\footnote" <> braces (nest 2 contents' <> optnl)
|
2011-07-10 09:13:10 -07:00
|
|
|
-- note: a \n before } needed when note ends with a Verbatim environment
|
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
|
2013-01-17 19:47:03 -08:00
|
|
|
|
|
|
|
-- Determine listings language from list of class attributes.
|
|
|
|
getListingsLanguage :: [String] -> Maybe String
|
|
|
|
getListingsLanguage [] = Nothing
|
2013-03-05 22:09:42 -08:00
|
|
|
getListingsLanguage (x:xs) = toListingsLanguage x <|> getListingsLanguage xs
|