{-# LANGUAGE ForeignFunctionInterface #-} {-# OPTIONS -Wall -O #-} module PixbufExtras (pixbufGetSizeInfoFile) where import Control.Applicative (Applicative, liftA, pure) import Data.Word import Foreign.C import Foreign.Marshal.Alloc import Foreign.Ptr import Foreign.Storable import Graphics.UI.Gtk.Gdk.Pixbuf () -- | Read file metadata and return image size pixbufGetSizeInfoFile :: FilePath -> IO (Maybe (Int, Int)) pixbufGetSizeInfoFile fp = withCString fp $ \cfp -> alloca $ \wp -> alloca $ \hp -> pixbufGetFileInfo cfp wp hp >>= ptrMaybeA (\_ -> peek wp >>= \w -> peek hp >>= \h -> return (w, h)) -- FIXME: the return value shall not be a Ptr to a Word. foreign import ccall "static gdk/gdkpixbuf.h gdk_pixbuf_get_file_info" pixbufGetFileInfo :: CString -> Ptr Int -> Ptr Int -> IO (Ptr Word) -- | Apply function if the pointer is not NULL ptrMaybeA :: Applicative m => (Ptr a -> m b) -> Ptr a -> m (Maybe b) ptrMaybeA f p | p == nullPtr = pure Nothing | otherwise = liftA Just $ f p