{- PkgSpec.hsc: Haskell bindings to libdpkg Copyright (C) 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.PkgSpec ( pkgSpecParsePkg ) 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 type FIXME = C'dpkg_error #callconv pkg_spec_parse_pkg , ccall unsafe , CString -> Ptr FIXME -> IO (Ptr ) -- FIXME: if NULL return, handle error pkgSpecParsePkg :: String -> IO C'pkginfo pkgSpecParsePkg p = alloca $ \derr -> withCString p (\pcstr -> c'pkg_spec_parse_pkg pcstr derr) >>= peek