{-# LINE 1 "src/Text/Bibutils.hsc" #-}
{-# CFILES cbits/stub.c #-}
{-# LINE 2 "src/Text/Bibutils.hsc" #-}
module Text.Bibutils
(
Bibl
, Param (..)
, bibl_init
, bibl_initparams
, bibl_read
, bibl_write
, bibl_readasis
, bibl_addtoasis
, bibl_readcorps
, bibl_addtocorps
, bibl_free
, bibl_freeparams
, bibl_reporterr
, numberOfRefs
, status
, setParam
, setFormatOpts
, setCharsetIn
, setCharsetOut
, setBOM
, unsetBOM
, setNoSplitTitle
, unsetNoSplitTitle
, setLatexOut
, unsetLatexOut
, setXmlOut
, unsetXmlOut
, setAddcount
, unsetAddcount
, setSinglerefperfile
, unsetSinglerefperfile
, setVerbose
, unsetVerbose
, BiblioIn
, mods_in
, bibtex_in
, ris_in
, endnote_in
, copac_in
, isi_in
, medline_in
, biblatex_in
, endnotexml_in
, BiblioOut
, mods_out
, bibtex_out
, ris_out
, endnote_out
, isi_out
, word2007_out
, adsab_out
, FormatOpt
, bibout_finalcomma
, bibout_singledash
, bibout_whitespace
, bibout_brackets
, bibout_uppercase
, bibout_strictkey
, modsout_dropkey
, Charset
, bibl_charset_unknown
, bibl_charset_unicode
, bibl_charset_gb18030
, bibl_charset_default
, Status
, bibl_ok
, bibl_err_badinput
, bibl_err_memerr
, bibl_err_cantopen
) where
import Control.Monad
import Foreign.C
import Foreign
newtype Bibl = Bibl { nrefs :: CLong }
instance Storable Bibl where
sizeOf _ = (24)
{-# LINE 129 "src/Text/Bibutils.hsc" #-}
alignment _ = 8
{-# LINE 130 "src/Text/Bibutils.hsc" #-}
peek p = (\hsc_ptr -> peekByteOff hsc_ptr 0) p >>= return . Bibl
{-# LINE 131 "src/Text/Bibutils.hsc" #-}
poke p (Bibl n) = (\hsc_ptr -> pokeByteOff hsc_ptr 0) p n
{-# LINE 132 "src/Text/Bibutils.hsc" #-}
bibl_init :: IO (ForeignPtr Bibl)
bibl_init
= alloca $ \p -> do
c_bibl_init p
newForeignPtr_ p
bibl_free :: ForeignPtr Bibl -> IO ()
bibl_free bibl = withForeignPtr bibl c_bibl_free
numberOfRefs :: ForeignPtr Bibl -> IO Int
numberOfRefs b
= withForeignPtr b $ \cb -> peek cb >>= return . fromIntegral . nrefs
data Param
= Param
{ redaformat :: CInt
, writeformat :: CInt
, charsetin :: CInt
, charsetin_src :: CUChar
, latexin :: CUChar
, utf8in :: CUChar
, xmlin :: CUChar
, nosplittitle :: CUChar
, charsetout :: CInt
, charsetout_src :: CUChar
, latexout :: CUChar
, utf8out :: CUChar
, utf8bom :: CUChar
, xmlout :: CUChar
, format_opts :: CInt
, addcount :: CInt
, output_raw :: CUChar
, verbose :: CUChar
, singlerefperfile :: CUChar
} deriving ( Show )
instance Storable Param where
sizeOf _ = (184)
{-# LINE 177 "src/Text/Bibutils.hsc" #-}
alignment _ = 8
{-# LINE 178 "src/Text/Bibutils.hsc" #-}
peek p = Param
`fmap` (\hsc_ptr -> peekByteOff hsc_ptr 0) p
{-# LINE 180 "src/Text/Bibutils.hsc" #-}
`ap` (\hsc_ptr -> peekByteOff hsc_ptr 4) p
{-# LINE 181 "src/Text/Bibutils.hsc" #-}
`ap` (\hsc_ptr -> peekByteOff hsc_ptr 8) p
{-# LINE 182 "src/Text/Bibutils.hsc" #-}
`ap` (\hsc_ptr -> peekByteOff hsc_ptr 12) p
{-# LINE 183 "src/Text/Bibutils.hsc" #-}
`ap` (\hsc_ptr -> peekByteOff hsc_ptr 13) p
{-# LINE 184 "src/Text/Bibutils.hsc" #-}
`ap` (\hsc_ptr -> peekByteOff hsc_ptr 14) p
{-# LINE 185 "src/Text/Bibutils.hsc" #-}
`ap` (\hsc_ptr -> peekByteOff hsc_ptr 15) p
{-# LINE 186 "src/Text/Bibutils.hsc" #-}
`ap` (\hsc_ptr -> peekByteOff hsc_ptr 16) p
{-# LINE 187 "src/Text/Bibutils.hsc" #-}
`ap` (\hsc_ptr -> peekByteOff hsc_ptr 20) p
{-# LINE 188 "src/Text/Bibutils.hsc" #-}
`ap` (\hsc_ptr -> peekByteOff hsc_ptr 24) p
{-# LINE 189 "src/Text/Bibutils.hsc" #-}
`ap` (\hsc_ptr -> peekByteOff hsc_ptr 25) p
{-# LINE 190 "src/Text/Bibutils.hsc" #-}
`ap` (\hsc_ptr -> peekByteOff hsc_ptr 26) p
{-# LINE 191 "src/Text/Bibutils.hsc" #-}
`ap` (\hsc_ptr -> peekByteOff hsc_ptr 27) p
{-# LINE 192 "src/Text/Bibutils.hsc" #-}
`ap` (\hsc_ptr -> peekByteOff hsc_ptr 28) p
{-# LINE 193 "src/Text/Bibutils.hsc" #-}
`ap` (\hsc_ptr -> peekByteOff hsc_ptr 32) p
{-# LINE 194 "src/Text/Bibutils.hsc" #-}
`ap` (\hsc_ptr -> peekByteOff hsc_ptr 36) p
{-# LINE 195 "src/Text/Bibutils.hsc" #-}
`ap` (\hsc_ptr -> peekByteOff hsc_ptr 40) p
{-# LINE 196 "src/Text/Bibutils.hsc" #-}
`ap` (\hsc_ptr -> peekByteOff hsc_ptr 41) p
{-# LINE 197 "src/Text/Bibutils.hsc" #-}
`ap` (\hsc_ptr -> peekByteOff hsc_ptr 42) p
{-# LINE 198 "src/Text/Bibutils.hsc" #-}
poke p (Param rf wf ci csi li ui xi nt co cso lo uo ub xo fo a raw v s) = do
(\hsc_ptr -> pokeByteOff hsc_ptr 0) p rf
{-# LINE 200 "src/Text/Bibutils.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 4) p wf
{-# LINE 201 "src/Text/Bibutils.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 8) p ci
{-# LINE 202 "src/Text/Bibutils.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 12) p csi
{-# LINE 203 "src/Text/Bibutils.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 13) p li
{-# LINE 204 "src/Text/Bibutils.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 14) p ui
{-# LINE 205 "src/Text/Bibutils.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 15) p xi
{-# LINE 206 "src/Text/Bibutils.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 16) p nt
{-# LINE 207 "src/Text/Bibutils.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 20) p co
{-# LINE 208 "src/Text/Bibutils.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 24) p cso
{-# LINE 209 "src/Text/Bibutils.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 25) p lo
{-# LINE 210 "src/Text/Bibutils.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 26) p uo
{-# LINE 211 "src/Text/Bibutils.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 27) p ub
{-# LINE 212 "src/Text/Bibutils.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 28) p xo
{-# LINE 213 "src/Text/Bibutils.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 32) p fo
{-# LINE 214 "src/Text/Bibutils.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 36) p a
{-# LINE 215 "src/Text/Bibutils.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 40) p raw
{-# LINE 216 "src/Text/Bibutils.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 41) p v
{-# LINE 217 "src/Text/Bibutils.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 42) p s
{-# LINE 218 "src/Text/Bibutils.hsc" #-}
bibl_initparams :: BiblioIn -> BiblioOut -> String -> IO (ForeignPtr Param)
bibl_initparams i o s
= alloca $ \p -> withCString s $ \cs -> do
c_bibl_initparams p (unBiblioIn i) (unBiblioOut o) cs
newForeignPtr_ p
bibl_freeparams :: ForeignPtr Param -> IO ()
bibl_freeparams param = withForeignPtr param c_bibl_freeparams
setParam :: ForeignPtr Param -> (Param -> Param) -> IO ()
setParam p f = withForeignPtr p $ \cp -> peek cp >>= poke cp . f
setCharsetIn :: ForeignPtr Param -> Charset -> IO ()
setCharsetIn p c
= setParam p $ \param -> param { charsetin = charset c }
setCharsetOut :: ForeignPtr Param -> Charset -> IO ()
setCharsetOut p c
= setParam p $ \param -> param { charsetout = charset c }
setFormatOpts :: ForeignPtr Param -> [FormatOpt] -> IO ()
setFormatOpts p os
= setParam p $ \param -> param { format_opts = unFormatOpt $ combineFormatOpts os }
setBOM :: ForeignPtr Param -> IO ()
setBOM p
= setParam p $ \param -> param { utf8bom = 1 }
unsetBOM :: ForeignPtr Param -> IO ()
unsetBOM p
= setParam p $ \param -> param { utf8bom = 0 }
setNoSplitTitle :: ForeignPtr Param -> IO ()
setNoSplitTitle p
= setParam p $ \param -> param { nosplittitle = 1 }
unsetNoSplitTitle :: ForeignPtr Param -> IO ()
unsetNoSplitTitle p
= setParam p $ \param -> param { nosplittitle = 0 }
setLatexOut :: ForeignPtr Param -> IO ()
setLatexOut p
= setParam p $ \param -> param { latexout = 1 }
unsetLatexOut :: ForeignPtr Param -> IO ()
unsetLatexOut p
= setParam p $ \param -> param { latexout = 0 }
setXmlOut :: ForeignPtr Param -> IO ()
setXmlOut p
= setParam p $ \param -> param { xmlout = 1 }
unsetXmlOut :: ForeignPtr Param -> IO ()
unsetXmlOut p
= setParam p $ \param -> param { xmlout = 0 }
setAddcount :: ForeignPtr Param -> IO ()
setAddcount p
= setParam p $ \param -> param { addcount = 1 }
unsetAddcount :: ForeignPtr Param -> IO ()
unsetAddcount p
= setParam p $ \param -> param { addcount = 0 }
setSinglerefperfile :: ForeignPtr Param -> IO ()
setSinglerefperfile p
= setParam p $ \param -> param { singlerefperfile = 1 }
unsetSinglerefperfile :: ForeignPtr Param -> IO ()
unsetSinglerefperfile p
= setParam p $ \param -> param { singlerefperfile = 0 }
setVerbose :: ForeignPtr Param -> IO ()
setVerbose p
= setParam p $ \param -> param { verbose = 1 }
unsetVerbose :: ForeignPtr Param -> IO ()
unsetVerbose p
= setParam p $ \param -> param { verbose = 0 }
bibl_read :: ForeignPtr Param -> ForeignPtr Bibl -> FilePath -> IO Status
bibl_read param bibl path
= withForeignPtr param $ \cparam ->
withForeignPtr bibl $ \cbibl ->
withCString path $ \cpath ->
withCString "r" $ \cmode -> do
cfile <- if path == "-"
then return c_stdin
else throwErrnoIfNull "fopen: " (fopen cpath cmode)
cint <- c_bibl_read cbibl cfile cpath cparam
when (path /= "-") $ fclose cfile >> return ()
return $ Status cint
bibl_write :: ForeignPtr Param -> ForeignPtr Bibl -> FilePath -> IO Status
bibl_write param bibl path
= withForeignPtr param $ \cparam ->
withForeignPtr bibl $ \cbibl ->
withCString "w" $ \cmode -> do
cfile <- if path == "-"
then return c_stdout
else withCString path $ throwErrnoIfNull "fopen: " . flip fopen cmode
cint <- c_bibl_write cbibl cfile cparam
when (path /= "-") $ fclose cfile >> return ()
return $ Status cint
bibl_readasis :: ForeignPtr Param -> FilePath -> IO ()
bibl_readasis param path
= withForeignPtr param $ \cparam ->
withCString path $ \cpath -> do
c_bibl_readasis cparam cpath
bibl_addtoasis :: ForeignPtr Param -> String -> IO ()
bibl_addtoasis param entry
= withForeignPtr param $ \cparam ->
withCString entry $ \centry -> do
c_bibl_addtoasis cparam centry
bibl_readcorps :: ForeignPtr Param -> FilePath -> IO ()
bibl_readcorps param path
= withForeignPtr param $ \cparam ->
withCString path $ \cpath -> do
c_bibl_readcorps cparam cpath
bibl_addtocorps :: ForeignPtr Param -> String -> IO ()
bibl_addtocorps param entry
= withForeignPtr param $ \cparam ->
withCString entry $ \centry -> do
c_bibl_addtocorps cparam centry
bibl_reporterr :: Status -> IO ()
bibl_reporterr (Status n) = c_bibl_reporterr n
newtype BiblioIn = BiblioIn { unBiblioIn :: CInt }
deriving ( Eq )
mods_in :: BiblioIn
mods_in = BiblioIn 100
bibtex_in :: BiblioIn
bibtex_in = BiblioIn 101
ris_in :: BiblioIn
ris_in = BiblioIn 102
endnote_in :: BiblioIn
endnote_in = BiblioIn 103
copac_in :: BiblioIn
copac_in = BiblioIn 104
isi_in :: BiblioIn
isi_in = BiblioIn 105
medline_in :: BiblioIn
medline_in = BiblioIn 106
endnotexml_in :: BiblioIn
endnotexml_in = BiblioIn 107
biblatex_in :: BiblioIn
biblatex_in = BiblioIn 108
{-# LINE 389 "src/Text/Bibutils.hsc" #-}
newtype BiblioOut = BiblioOut { unBiblioOut :: CInt }
deriving ( Eq )
mods_out :: BiblioOut
mods_out = BiblioOut 200
bibtex_out :: BiblioOut
bibtex_out = BiblioOut 201
ris_out :: BiblioOut
ris_out = BiblioOut 202
endnote_out :: BiblioOut
endnote_out = BiblioOut 203
isi_out :: BiblioOut
isi_out = BiblioOut 204
word2007_out :: BiblioOut
word2007_out = BiblioOut 205
adsab_out :: BiblioOut
adsab_out = BiblioOut 206
{-# LINE 402 "src/Text/Bibutils.hsc" #-}
newtype FormatOpt = FormatOpt { unFormatOpt :: CInt }
{-# LINE 406 "src/Text/Bibutils.hsc" #-}
bibout_finalcomma :: FormatOpt
bibout_finalcomma = FormatOpt 2
bibout_singledash :: FormatOpt
bibout_singledash = FormatOpt 4
bibout_whitespace :: FormatOpt
bibout_whitespace = FormatOpt 8
bibout_brackets :: FormatOpt
bibout_brackets = FormatOpt 16
bibout_uppercase :: FormatOpt
bibout_uppercase = FormatOpt 32
bibout_strictkey :: FormatOpt
bibout_strictkey = FormatOpt 64
modsout_dropkey :: FormatOpt
modsout_dropkey = FormatOpt 512
{-# LINE 416 "src/Text/Bibutils.hsc" #-}
newtype Status = Status { status :: CInt }
deriving ( Eq, Show )
bibl_ok :: Status
bibl_ok = Status 0
bibl_err_badinput :: Status
bibl_err_badinput = Status (-1)
bibl_err_memerr :: Status
bibl_err_memerr = Status (-2)
bibl_err_cantopen :: Status
bibl_err_cantopen = Status (-3)
{-# LINE 426 "src/Text/Bibutils.hsc" #-}
newtype Charset = Charset { charset :: CInt } deriving ( Eq )
bibl_charset_unknown :: Charset
bibl_charset_unknown = Charset (-1)
bibl_charset_unicode :: Charset
bibl_charset_unicode = Charset (-2)
bibl_charset_gb18030 :: Charset
bibl_charset_gb18030 = Charset (-3)
bibl_charset_default :: Charset
bibl_charset_default = Charset (-2)
{-# LINE 435 "src/Text/Bibutils.hsc" #-}
combineFormatOpts :: [FormatOpt] -> FormatOpt
combineFormatOpts = FormatOpt . foldr ((.|.) . unFormatOpt) 0
{-# LINE 441 "src/Text/Bibutils.hsc" #-}
{-# LINE 442 "src/Text/Bibutils.hsc" #-}
{-# LINE 443 "src/Text/Bibutils.hsc" #-}
foreign import ccall unsafe "bibl_init"
c_bibl_init :: Ptr Bibl -> IO ()
foreign import ccall unsafe "bibl_free"
c_bibl_free :: Ptr Bibl -> IO ()
foreign import ccall unsafe "bibl_initparams"
c_bibl_initparams :: Ptr Param -> CInt -> CInt -> CString -> IO ()
foreign import ccall unsafe "bibl_freeparams"
c_bibl_freeparams :: Ptr Param -> IO ()
foreign import ccall unsafe "bibl_read"
c_bibl_read :: Ptr Bibl -> Ptr CFile -> CString -> Ptr Param -> IO CInt
foreign import ccall unsafe "bibl_write"
c_bibl_write :: Ptr Bibl -> Ptr CFile -> Ptr Param -> IO CInt
foreign import ccall unsafe "bibl_readasis"
c_bibl_readasis :: Ptr Param -> CString -> IO ()
foreign import ccall unsafe "bibl_addtoasis"
c_bibl_addtoasis :: Ptr Param -> CString -> IO ()
foreign import ccall unsafe "bibl_readcorps"
c_bibl_readcorps :: Ptr Param -> CString -> IO ()
foreign import ccall unsafe "bibl_addtocorps"
c_bibl_addtocorps :: Ptr Param -> CString -> IO ()
foreign import ccall unsafe "bibl_reporterr"
c_bibl_reporterr :: CInt -> IO ()
foreign import ccall unsafe "fopen"
fopen :: CString -> CString -> IO (Ptr CFile)
foreign import ccall unsafe "fclose"
fclose :: Ptr CFile -> IO CInt
foreign import ccall unsafe "c_stdin" c_stdin :: Ptr CFile
foreign import ccall unsafe "c_stdout" c_stdout :: Ptr CFile