Don't expose Text.Pandoc.Biblio module unless citeproc option is selected.

git-svn-id: https://pandoc.googlecode.com/svn/trunk@1408 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
fiddlosopher 2008-08-12 01:23:17 +00:00
parent 17a41e6ebc
commit aeaf5e5108
2 changed files with 2 additions and 9 deletions

View file

@ -1,4 +1,4 @@
{-# LANGUAGE PatternGuards, CPP #-} {-# LANGUAGE PatternGuards #-}
{- {-
Copyright (C) 2008 Andrea Rossato <andrea.rossato@ing.unitn.it> Copyright (C) 2008 Andrea Rossato <andrea.rossato@ing.unitn.it>
@ -27,7 +27,6 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
Portability : portable Portability : portable
-} -}
#ifdef _CITEPROC
module Text.Pandoc.Biblio ( processBiblio ) where module Text.Pandoc.Biblio ( processBiblio ) where
import Control.Monad ( when ) import Control.Monad ( when )
@ -35,11 +34,6 @@ import Data.List
import Text.CSL import Text.CSL
import Text.Pandoc.Definition import Text.Pandoc.Definition
#else
module Text.Pandoc.Biblio () where
#endif
#ifdef _CITEPROC
-- | Process a 'Pandoc' document by adding citations formatted -- | Process a 'Pandoc' document by adding citations formatted
-- according to a CSL style, using 'citeproc' from citeproc-hs. -- according to a CSL style, using 'citeproc' from citeproc-hs.
processBiblio :: String -> [Reference] -> Pandoc -> IO Pandoc processBiblio :: String -> [Reference] -> Pandoc -> IO Pandoc
@ -70,4 +64,3 @@ processCite cs il
getCite :: Inline -> [[(String,String)]] getCite :: Inline -> [[(String,String)]]
getCite i | Cite t _ <- i = [t] getCite i | Cite t _ <- i = [t]
| otherwise = [] | otherwise = []
#endif

View file

@ -156,12 +156,12 @@ Library
Other-Modules: Text.Pandoc.UTF8 Other-Modules: Text.Pandoc.UTF8
if flag(citeproc) if flag(citeproc)
Build-depends: citeproc-hs Build-depends: citeproc-hs
Exposed-Modules: Text.Pandoc.Biblio
cpp-options: -D_CITEPROC cpp-options: -D_CITEPROC
Build-Depends: parsec < 3, xhtml, mtl, network, filepath, process, directory, Build-Depends: parsec < 3, xhtml, mtl, network, filepath, process, directory,
template-haskell, bytestring template-haskell, bytestring
Hs-Source-Dirs: . Hs-Source-Dirs: .
Exposed-Modules: Text.Pandoc, Exposed-Modules: Text.Pandoc,
Text.Pandoc.Biblio,
Text.Pandoc.Blocks, Text.Pandoc.Blocks,
Text.Pandoc.Definition, Text.Pandoc.Definition,
Text.Pandoc.CharacterReferences, Text.Pandoc.CharacterReferences,