diff options
-rw-r--r-- | src/Text/Pandoc.hs | 1 | ||||
-rw-r--r-- | src/Text/Pandoc/Shared.hs | 10 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/LaTeX.hs | 118 | ||||
-rw-r--r-- | src/pandoc.hs | 37 | ||||
-rw-r--r-- | templates/latex.template | 18 |
5 files changed, 166 insertions, 18 deletions
diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs index 7d3468461..61d1098b9 100644 --- a/src/Text/Pandoc.hs +++ b/src/Text/Pandoc.hs @@ -97,6 +97,7 @@ module Text.Pandoc , WriterOptions (..) , HTMLSlideVariant (..) , HTMLMathMethod (..) + , CiteMethod (..) , defaultWriterOptions -- * Rendering templates and default templates , module Text.Pandoc.Templates diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index ee959931d..1975b7e4c 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -66,6 +66,7 @@ module Text.Pandoc.Shared ( headerShift, -- * Writer options HTMLMathMethod (..), + CiteMethod (..), ObfuscationMethod (..), HTMLSlideVariant (..), WriterOptions (..), @@ -472,6 +473,11 @@ data HTMLMathMethod = PlainMath | MathJax String -- url of MathJax.js deriving (Show, Read, Eq) +data CiteMethod = Citeproc -- use citeproc to render them + | Natbib -- output natbib cite commands + | Biblatex -- output biblatex cite commands + deriving (Show, Read, Eq) + -- | Methods for obfuscating email addresses in HTML. data ObfuscationMethod = NoObfuscation | ReferenceObfuscation @@ -507,6 +513,8 @@ data WriterOptions = WriterOptions , writerIdentifierPrefix :: String -- ^ Prefix for section & note ids in HTML , writerSourceDirectory :: FilePath -- ^ Directory path of 1st source file , writerUserDataDir :: Maybe FilePath -- ^ Path of user data directory + , writerCiteMethod :: CiteMethod -- ^ How to print cites + , writerBiblioFile :: String -- ^ Biblio file to use for citations } deriving Show -- | Default writer options. @@ -533,6 +541,8 @@ defaultWriterOptions = , writerIdentifierPrefix = "" , writerSourceDirectory = "." , writerUserDataDir = Nothing + , writerCiteMethod = Citeproc + , writerBiblioFile = "" } -- diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 0f5ae0eb2..e791d1332 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -32,7 +32,7 @@ import Text.Pandoc.Definition import Text.Pandoc.Shared import Text.Pandoc.Templates import Text.Printf ( printf ) -import Data.List ( (\\), isSuffixOf, isPrefixOf, intersperse ) +import Data.List ( (\\), isSuffixOf, isPrefixOf, intersperse, intercalate ) import Data.Char ( toLower ) import Control.Monad.State import Text.PrettyPrint.HughesPJ hiding ( Str ) @@ -76,7 +76,16 @@ pandocToLaTeX options (Pandoc (Meta title authors date) blocks) = do body <- blockListToLaTeX blocks let main = render body st <- get - let context = writerVariables options ++ + let biblio = takeWhile ((/=) '.') $ writerBiblioFile options + citecontext = case writerCiteMethod options of + Natbib -> [ ("biblio", biblio) + , ("natbib", "yes") + ] + Biblatex -> [ ("biblio", biblio) + , ("biblatex", "yes") + ] + _ -> [] + context = writerVariables options ++ [ ("toc", if writerTableOfContents options then "yes" else "") , ("body", main) , ("title", titletext) @@ -91,7 +100,8 @@ pandocToLaTeX options (Pandoc (Meta title authors date) blocks) = do [ ("url", "yes") | stUrl st ] ++ [ ("numbersections", "yes") | writerNumberSections options ] ++ [ ("lhs", "yes") | stLHS st ] ++ - [ ("graphics", "yes") | stGraphics st ] + [ ("graphics", "yes") | stGraphics st ] ++ + citecontext return $ if writerStandalone options then renderTemplate context template else main @@ -298,8 +308,14 @@ inlineToLaTeX (Subscript lst) = do return $ inCmd "textsubscr" contents inlineToLaTeX (SmallCaps lst) = inlineListToLaTeX (deVerb lst) >>= return . inCmd "textsc" -inlineToLaTeX (Cite _ lst) = - inlineListToLaTeX lst +inlineToLaTeX (Cite cits lst) = do + st <- get + let opts = stOptions st + case writerCiteMethod opts of + Natbib -> citationsToNatbib cits + Biblatex -> citationsToBiblatex cits + _ -> inlineListToLaTeX lst + inlineToLaTeX (Code str) = do st <- get when (stInNote st) $ modify $ \s -> s{ stVerbInNote = True } @@ -355,3 +371,95 @@ inlineToLaTeX (Note contents) = do let optNewline = "\\end{Verbatim}" `isSuffixOf` rawnote return $ text "\\footnote{" <> text rawnote <> (if optNewline then char '\n' else empty) <> char '}' + + +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 + pdoc <- inlineListToLaTeX p + sdoc <- inlineListToLaTeX s + 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 diff --git a/src/pandoc.hs b/src/pandoc.hs index 13f285f15..87e72298a 100644 --- a/src/pandoc.hs +++ b/src/pandoc.hs @@ -116,7 +116,8 @@ data Opt = Opt , optIdentifierPrefix :: String , optIndentedCodeClasses :: [String] -- ^ Default classes for indented code blocks , optDataDir :: Maybe FilePath - , optBibliography :: [Reference] + , optCiteMethod :: CiteMethod -- ^ Method to output cites + , optBibliography :: [String] , optCslFile :: FilePath } @@ -154,6 +155,7 @@ defaultOpts = Opt , optIdentifierPrefix = "" , optIndentedCodeClasses = [] , optDataDir = Nothing + , optCiteMethod = Citeproc , optBibliography = [] , optCslFile = "" } @@ -453,14 +455,7 @@ options = "" -- "Print default template for FORMAT" , Option "" ["bibliography"] (ReqArg - (\arg opt -> do - refs <- catch (readBiblioFile arg) $ \e -> do - UTF8.hPutStrLn stderr $ - "Error reading bibliography `" ++ arg ++ "'" - UTF8.hPutStrLn stderr $ show e - exitWith (ExitFailure 23) - return opt { optBibliography = - optBibliography opt ++ refs } ) + (\arg opt -> return opt { optBibliography = (optBibliography opt) ++ [arg] }) "FILENAME") "" , Option "" ["csl"] @@ -468,6 +463,14 @@ options = (\arg opt -> return opt { optCslFile = arg }) "FILENAME") "" + , Option "" ["natbib"] + (NoArg + (\opt -> return opt { optCiteMethod = Natbib })) + "" -- "Use natbib cite commands in LaTeX output" + , Option "" ["biblatex"] + (NoArg + (\opt -> return opt { optCiteMethod = Biblatex })) + "" -- "Use biblatex cite commands in LaTeX output" , Option "" ["data-dir"] (ReqArg (\arg opt -> return opt { optDataDir = Just arg }) @@ -618,8 +621,9 @@ main = do , optIdentifierPrefix = idPrefix , optIndentedCodeClasses = codeBlockClasses , optDataDir = mbDataDir - , optBibliography = refs + , optBibliography = reffiles , optCslFile = cslfile + , optCiteMethod = citeMethod } = opts when dumpArgs $ @@ -693,6 +697,11 @@ main = do return $ ("mathml-script", s) : variables' _ -> return variables' + refs <- mapM (\f -> catch (readBiblioFile f) $ \e -> do + UTF8.hPutStrLn stderr $ "Error reading bibliography `" ++ f ++ "'" + UTF8.hPutStrLn stderr $ show e + exitWith (ExitFailure 23)) reffiles >>= \rs -> return $ concat rs + let sourceDir = if null sources then "." else takeDirectory (head sources) @@ -729,6 +738,8 @@ main = do writerSlideVariant = slideVariant, writerIncremental = incremental, writerXeTeX = xetex, + writerCiteMethod = citeMethod, + writerBiblioFile = head reffiles, writerIgnoreNotes = False, writerNumberSections = numberSections, writerSectionDivs = sectionDivs, @@ -766,9 +777,8 @@ main = do let doc' = foldr ($) doc transforms doc'' <- do - if null refs - then return doc' - else do + if citeMethod == Citeproc && not (null refs) + then do csldir <- getAppUserDataDirectory "csl" cslfile' <- if null cslfile then findDataFile datadir "default.csl" @@ -781,6 +791,7 @@ main = do (replaceExtension cslfile "csl") csldir processBiblio cslfile' refs doc' + else return doc' writerOutput <- writer writerOptions doc'' diff --git a/templates/latex.template b/templates/latex.template index eeb2f9e4b..8797871e8 100644 --- a/templates/latex.template +++ b/templates/latex.template @@ -13,6 +13,16 @@ $else$ \usepackage[mathletters]{ucs} \usepackage[utf8x]{inputenc} $endif$ +$if(natbib)$ +\usepackage{natbib} +\bibliographystyle{plainnat} +$endif$ +$if(biblatex)$ +\usepackage{biblatex} +$if(biblio)$ +\bibliography{$biblio$} +$endif$ +$endif$ $if(lhs)$ \usepackage{listings} \lstnewenvironment{code}{\lstset{language=Haskell,basicstyle=\small\ttfamily}}{} @@ -94,6 +104,14 @@ $if(toc)$ $endif$ $body$ +$if(biblio)$ +$if(natbib)$ +\bibliography{$biblio$} +$endif$ +$endif$ +$if(biblatex)$ +\printbibliography +$endif$ $for(include-after)$ $include-after$ |