aboutsummaryrefslogtreecommitdiff
path: root/src/pandoc.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2010-11-20 08:11:30 -0800
committerJohn MacFarlane <jgm@berkeley.edu>2010-11-20 08:11:30 -0800
commit3eef887dfa4e47095c4be9b2bdbf67c002e29f90 (patch)
treefad4a1a9c0100201f4556bb349ebaced4b986639 /src/pandoc.hs
parent46121aa2e1ad9afd8b06684fa9a36a00a73c106d (diff)
downloadpandoc-3eef887dfa4e47095c4be9b2bdbf67c002e29f90.tar.gz
Citation related changes.
* Don't look for bibliography in ~/.pandoc. Reason: doing this requires a read + parse of the bibliography even when the document doesn't use citations. This is a big performance drag on regular pandoc invocations. * Only look for default.csl if the document contains references. Reason: avoids the need to read and parse csl file when the document contains no references anyway. * Removed findFirstFile from Shared.
Diffstat (limited to 'src/pandoc.hs')
-rw-r--r--src/pandoc.hs31
1 files changed, 9 insertions, 22 deletions
diff --git a/src/pandoc.hs b/src/pandoc.hs
index ab4110b42..66a09b309 100644
--- a/src/pandoc.hs
+++ b/src/pandoc.hs
@@ -32,7 +32,7 @@ module Main where
import Text.Pandoc
import Text.Pandoc.S5 (s5HeaderIncludes)
import Text.Pandoc.Shared ( tabFilter, ObfuscationMethod (..), readDataFile,
- headerShift, findDataFile, findFirstFile )
+ headerShift, findDataFile )
#ifdef _HIGHLIGHTING
import Text.Pandoc.Highlighting ( languages )
#endif
@@ -767,25 +767,6 @@ main = do
return $ ("mathml-script", s) : variables'
_ -> return variables'
-#ifdef _CITEPROC
- cslfile' <- if null cslfile
- then findDataFile datadir "default.csl"
- else return cslfile
- csl <- readCSLFile cslfile'
- refs' <- if null refs
- then do
- f <- findFirstFile datadir
- ["biblio.xml","biblio.json","biblio.bib"]
- case f of
- Just x -> catch (readBiblioFile x) $ \e -> do
- UTF8.hPutStrLn stderr $
- "Error reading bibliography `" ++ x ++ "'"
- UTF8.hPutStrLn stderr $ show e
- exitWith (ExitFailure 23) >> return []
- Nothing -> return []
- else return refs
-#endif
-
let sourceDir = if null sources
then "."
else takeDirectory (head sources)
@@ -803,7 +784,7 @@ main = do
lhsExtension sources,
stateStandalone = standalone',
#ifdef _CITEPROC
- stateCitations = map refId refs',
+ stateCitations = map refId refs,
#endif
stateSmart = smart || writerName' `elem`
["latex", "context", "latex+lhs", "man"],
@@ -863,7 +844,13 @@ main = do
doc'' <- do
#ifdef _CITEPROC
- processBiblio csl refs' doc'
+ if null refs
+ then return doc'
+ else do
+ cslfile' <- if null cslfile
+ then findDataFile datadir "default.csl"
+ else return cslfile
+ processBiblio cslfile' refs doc'
#else
return doc'
#endif