{- DB.hsc: Haskell bindings to libdpkg Copyright (C) 2011, 2012 Clint Adams This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA -} {-# LANGUAGE CPP, ForeignFunctionInterface #-} #include module Debian.Dpkg.DB ( msdbInit , setDbDir , pkgList , parseVersion , c'parseversion , c'versioncompare ) where #strict_import import Foreign.Ptr (nullPtr) import Foreign.C.String (withCString, peekCString) import Foreign.Marshal.Utils (with) import Control.Monad (liftM, join) import Control.Monad.Loops (unfoldrM) import qualified Data.ByteString as BS import Debian.Dpkg.Types #include #callconv modstatdb_open , ccall unsafe , CInt -> IO () #callconv push_error_context , ccall unsafe , IO () #callconv dpkg_set_progname , ccall unsafe , CString -> IO () #callconv dpkg_db_set_dir , ccall unsafe , CString -> IO () #callconv pkg_db_iter_new , ccall unsafe , IO (Ptr ) #callconv pkg_db_iter_next_pkg , ccall unsafe , Ptr -> IO (Ptr ) msdbInit :: IO () msdbInit = do c'push_error_context c'modstatdb_open 0 withCString "haskell-dpkg" c'dpkg_set_progname setDbDir :: String -> IO () setDbDir x = withCString x c'dpkg_db_set_dir pkgDbIterNext :: Ptr C'pkgiterator -> IO (Maybe (Ptr C'pkginfo, Ptr C'pkgiterator)) pkgDbIterNext i = do pptr <- c'pkg_db_iter_next_pkg i if pptr == nullPtr then return Nothing else return $ Just (pptr, i) pkgpList :: IO [Ptr C'pkginfo] pkgpList = c'pkg_db_iter_new >>= unfoldrM (pkgDbIterNext) pkgList :: IO [C'pkginfo] pkgList = pkgpList >>= mapM peek #callconv parseversion , ccall unsafe , Ptr C'versionrevision -> CString -> Ptr C'dpkg_error -> IO CInt #callconv versioncompare , ccall unsafe , Ptr C'versionrevision -> Ptr C'versionrevision -> IO CInt parseVersion :: BS.ByteString -> IO (Either String C'versionrevision) parseVersion verstr = BS.useAsCString verstr $ \vercstr -> alloca $ \vrptr -> alloca $ \deptr -> do i <- c'parseversion vrptr vercstr deptr vr <- peek vrptr if i == 0 then return $ Right vr else do de <- peek deptr errmsg <- peekCString (c'dpkg_error'str de) if (c'dpkg_error'type de) == 1 then return $ Right vr else return $ Left errmsg