{-# LANGUAGE CPP, ForeignFunctionInterface, PatternGuards #-} ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Input.Bibutils -- Copyright : (C) 2008 Andrea Rossato -- License : BSD3 -- -- Maintainer : andrea.rossato@unitn.it -- Stability : unstable -- Portability : unportable -- ----------------------------------------------------------------------------- module Text.CSL.Input.Bibutils ( readBiblioFile ) where import Text.CSL.Reference import Text.CSL.Input.Json import Text.CSL.Input.MODS import System.FilePath ( takeExtension, () ) #ifdef USE_BIBUTILS import Data.Char import System.Directory ( getTemporaryDirectory, removeFile ) import System.IO import Text.Bibutils #endif -- | Read a file with a bibliographic database. The database format -- is recognized by the file extension. -- -- Supported formats are: @json@, @mods@, @bibtex@, @biblatex@, @ris@, -- @endnote@, @endnotexml@, @isi@, @medline@, and @copac@. readBiblioFile :: FilePath -> IO [Reference] #ifdef USE_BIBUTILS readBiblioFile f = case getExt f of ".mods" -> readBiblioFile' f mods_in ".bib" -> readBiblioFile' f bibtex_in ".bbx" -> readBiblioFile' f biblatex_in ".ris" -> readBiblioFile' f ris_in ".enl" -> readBiblioFile' f endnote_in ".xml" -> readBiblioFile' f endnotexml_in ".wos" -> readBiblioFile' f isi_in ".medline" -> readBiblioFile' f medline_in ".copac" -> readBiblioFile' f copac_in ".json" -> readJsonInput f _ -> error $ "citeproc: the format of the bibliographic database could not be recognized\n" ++ "using the file extension." #else readBiblioFile f | ".mods" <- getExt f = readModsCollectionFile f | ".json" <- getExt f = readJsonInput f | otherwise = error $ "citeproc: Bibliography format not supported.\n" ++ "citeproc-hs was not compiled with bibutils support." #endif getExt :: String -> String getExt = takeExtension . map toLower #ifdef USE_BIBUTILS readBiblioFile' :: FilePath -> BiblioIn -> IO [Reference] readBiblioFile' fin bin | bin == mods_in = readModsCollectionFile fin | otherwise = do tdir <- getTemporaryDirectory (f,h) <- openTempFile tdir "citeproc.txt" hClose h let tfile = tdir f param <- bibl_initparams bin mods_out "hs-bibutils" bibl <- bibl_init unsetBOM param setNoSplitTitle param setCharsetIn param bibl_charset_unicode setCharsetOut param bibl_charset_unicode _ <- bibl_read param bibl fin _ <- bibl_write param bibl tfile bibl_free bibl bibl_freeparams param refs <- readModsCollectionFile tfile removeFile tfile return refs #endif