{- DB.hsc: Haskell bindings to libdpkg Copyright (C) 2011 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 , pkgDbFind , pkgList , getConfigVersion ) 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 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 , 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 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 pkg_db_find , ccall unsafe , CString -> IO (Ptr ) pkgDbFind :: String -> IO C'pkginfo pkgDbFind p = withCString p c'pkg_db_find >>= peek getConfigVersion :: C'pkginfo -> IO String getConfigVersion p = do v <- peekCString (c'versionrevision'version vr) r <- peekCString (c'versionrevision'revision vr) return $ nonZeroEpoch e ++ v ++ nonNativeRevision r where nonZeroEpoch e = if e == 0 then "" else (show e) ++ ":" nonNativeRevision r = if r == "" then r else "-" ++ r e = fromIntegral (c'versionrevision'epoch vr) vr = c'pkginfo'configversion p