module Graphics.UI.Gtk.Gdk.Pixbuf (
Pixbuf,
PixbufClass,
castToPixbuf, gTypePixbuf,
toPixbuf,
PixbufError(..),
Colorspace(..),
pixbufNew,
pixbufNewFromData,
pixbufNewFromFile,
pixbufNewFromFileAtSize,
pixbufNewFromFileAtScale,
pixbufNewFromInline,
InlineImage,
pixbufNewSubpixbuf,
pixbufNewFromXPMData,
pixbufGetColorSpace,
pixbufGetNChannels,
pixbufGetHasAlpha,
pixbufGetBitsPerSample,
PixbufData,
pixbufGetPixels,
pixbufGetWidth,
pixbufGetHeight,
pixbufGetRowstride,
pixbufGetOption,
ImageFormat,
pixbufGetFormats,
pixbufSave,
pixbufCopy,
InterpType(..),
pixbufScaleSimple,
pixbufScale,
pixbufComposite,
pixbufFlipHorizontally,
pixbufFlipHorazontally,
pixbufFlipVertically,
pixbufRotateSimple,
PixbufRotation(..),
pixbufAddAlpha,
pixbufCopyArea,
pixbufFill,
pixbufGetFromDrawable,
pixbufRenderThresholdAlpha,
pixbufRenderPixmapAndMaskForColormap
) where
import Control.Monad (liftM)
import Data.Ix
import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.GDateTime
import System.Glib.GObject
import Graphics.UI.Gtk.Types
import Graphics.UI.Gtk.General.Structs (Rectangle(..))
import System.Glib.GError (GError(..), GErrorClass(..), GErrorDomain,
propagateGError)
import Graphics.UI.Gtk.Gdk.PixbufData ( PixbufData, mkPixbufData )
import Graphics.UI.Gtk.Gdk.Pixmap (Bitmap, Pixmap)
data PixbufError = PixbufErrorCorruptImage
| PixbufErrorInsufficientMemory
| PixbufErrorBadOption
| PixbufErrorUnknownType
| PixbufErrorUnsupportedOperation
| PixbufErrorFailed
deriving (Enum)
data Colorspace = ColorspaceRgb
deriving (Enum)
pixbufGetColorSpace :: Pixbuf -> IO Colorspace
pixbufGetColorSpace pb = liftM (toEnum . fromIntegral) $
(\(Pixbuf arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_pixbuf_get_colorspace argPtr1) pb
pixbufGetNChannels :: Pixbuf -> IO Int
pixbufGetNChannels pb = liftM fromIntegral $
(\(Pixbuf arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_pixbuf_get_n_channels argPtr1) pb
pixbufGetHasAlpha :: Pixbuf -> IO Bool
pixbufGetHasAlpha pb =
liftM toBool $ (\(Pixbuf arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_pixbuf_get_has_alpha argPtr1) pb
pixbufGetBitsPerSample :: Pixbuf -> IO Int
pixbufGetBitsPerSample pb = liftM fromIntegral $
(\(Pixbuf arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_pixbuf_get_bits_per_sample argPtr1) pb
pixbufGetPixels :: Storable e => Pixbuf -> IO (PixbufData Int e)
pixbufGetPixels pb = do
pixPtr_ <- (\(Pixbuf arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_pixbuf_get_pixels argPtr1) pb
chan <- pixbufGetNChannels pb
bits <- pixbufGetBitsPerSample pb
w <- pixbufGetWidth pb
h <- pixbufGetHeight pb
r <- pixbufGetRowstride pb
let pixPtr = castPtr pixPtr_
let bytes = (h1)*r+w*((chan*bits+7) `div` 8)
return (mkPixbufData pb pixPtr bytes)
pixbufGetWidth :: Pixbuf -> IO Int
pixbufGetWidth pb = liftM fromIntegral $
(\(Pixbuf arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_pixbuf_get_width argPtr1) pb
pixbufGetHeight :: Pixbuf -> IO Int
pixbufGetHeight pb = liftM fromIntegral $
(\(Pixbuf arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_pixbuf_get_height argPtr1) pb
pixbufGetRowstride :: Pixbuf -> IO Int
pixbufGetRowstride pb = liftM fromIntegral $
(\(Pixbuf arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_pixbuf_get_rowstride argPtr1) pb
pixbufGetOption :: Pixbuf -> String -> IO (Maybe String)
pixbufGetOption pb key = withUTFString key $ \strPtr -> do
resPtr <- (\(Pixbuf arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gdk_pixbuf_get_option argPtr1 arg2) pb strPtr
if (resPtr==nullPtr) then return Nothing else
liftM Just $ peekUTFString resPtr
pixbufErrorDomain :: GErrorDomain
pixbufErrorDomain = gdk_pixbuf_error_quark
instance GErrorClass PixbufError where
gerrorDomain _ = pixbufErrorDomain
pixbufNewFromFile :: FilePath -> IO Pixbuf
pixbufNewFromFile fname =
wrapNewGObject mkPixbuf $
propagateGError $ \errPtrPtr ->
withUTFString fname $ \strPtr ->
gdk_pixbuf_new_from_file
strPtr errPtrPtr
pixbufNewFromFileAtSize :: String -> Int -> Int -> IO Pixbuf
pixbufNewFromFileAtSize filename width height =
wrapNewGObject mkPixbuf $
propagateGError $ \errPtrPtr ->
withUTFString filename $ \filenamePtr ->
gdk_pixbuf_new_from_file_at_size
filenamePtr
(fromIntegral width)
(fromIntegral height)
errPtrPtr
pixbufNewFromFileAtScale ::
String
-> Int
-> Int
-> Bool
-> IO Pixbuf
pixbufNewFromFileAtScale filename width height preserveAspectRatio =
wrapNewGObject mkPixbuf $
propagateGError $ \errPtrPtr ->
withUTFString filename $ \filenamePtr ->
gdk_pixbuf_new_from_file_at_scale
filenamePtr
(fromIntegral width)
(fromIntegral height)
(fromBool preserveAspectRatio)
errPtrPtr
type ImageFormat = String
pixbufGetFormats :: [ImageFormat]
pixbufGetFormats = ["png","bmp","wbmp", "gif","ico","ani","jpeg","pnm",
"ras","tiff","xpm","xbm","tga"]
pixbufSave :: Pixbuf -> FilePath -> ImageFormat -> [(String, String)] ->
IO ()
pixbufSave pb fname iType options =
let (keys, values) = unzip options in
let optLen = length keys in
propagateGError $ \errPtrPtr ->
withUTFString fname $ \fnPtr ->
withUTFString iType $ \tyPtr ->
withUTFStringArray0 keys $ \keysPtr ->
withUTFStringArray values $ \valuesPtr -> do
(\(Pixbuf arg1) arg2 arg3 arg4 arg5 arg6 -> withForeignPtr arg1 $ \argPtr1 ->gdk_pixbuf_savev argPtr1 arg2 arg3 arg4 arg5 arg6)
pb fnPtr tyPtr keysPtr valuesPtr errPtrPtr
return ()
pixbufNew :: Colorspace -> Bool -> Int -> Int -> Int -> IO Pixbuf
pixbufNew colorspace hasAlpha bitsPerSample width height =
wrapNewGObject mkPixbuf $
gdk_pixbuf_new ((fromIntegral . fromEnum) colorspace)
(fromBool hasAlpha) (fromIntegral bitsPerSample) (fromIntegral width)
(fromIntegral height)
pixbufNewFromData :: Ptr CUChar -> Colorspace -> Bool -> Int -> Int -> Int -> Int -> IO Pixbuf
pixbufNewFromData imData cSpace hasAlpha bitsPerSample width height rowStride
= wrapNewGObject mkPixbuf $
gdk_pixbuf_new_from_data
imData
(fromIntegral . fromEnum $ cSpace)
(fromBool hasAlpha)
(fromIntegral bitsPerSample)
(fromIntegral width)
(fromIntegral height)
(fromIntegral rowStride)
nullFunPtr nullPtr
pixbufNewFromXPMData :: [String] -> IO Pixbuf
pixbufNewFromXPMData s =
withUTFStringArray0 s $ \strsPtr ->
wrapNewGObject mkPixbuf $ gdk_pixbuf_new_from_xpm_data strsPtr
data InlineImage = InlineImage
pixbufNewFromInline :: Ptr InlineImage -> IO Pixbuf
pixbufNewFromInline iPtr = alloca $ \errPtrPtr -> do
pbPtr <- gdk_pixbuf_new_from_inline (1) (castPtr iPtr)
(fromBool False) (castPtr errPtrPtr)
if pbPtr/=nullPtr then wrapNewGObject mkPixbuf (return pbPtr)
else do
errPtr <- peek errPtrPtr
(GError dom code msg) <- peek errPtr
error msg
pixbufNewSubpixbuf :: Pixbuf -> Int -> Int -> Int -> Int -> IO Pixbuf
pixbufNewSubpixbuf pb srcX srcY height width =
wrapNewGObject mkPixbuf $ do
pbPtr <- (\(Pixbuf arg1) arg2 arg3 arg4 arg5 -> withForeignPtr arg1 $ \argPtr1 ->gdk_pixbuf_new_subpixbuf argPtr1 arg2 arg3 arg4 arg5) pb
(fromIntegral srcX) (fromIntegral srcY)
(fromIntegral height) (fromIntegral width)
if pbPtr==nullPtr then error "pixbufNewSubpixbuf: invalid bounds"
else return pbPtr
pixbufCopy :: Pixbuf -> IO Pixbuf
pixbufCopy pb = wrapNewGObject mkPixbuf $ (\(Pixbuf arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_pixbuf_copy argPtr1) pb
data InterpType = InterpNearest
| InterpTiles
| InterpBilinear
| InterpHyper
deriving (Enum)
pixbufScaleSimple ::
Pixbuf
-> Int
-> Int
-> InterpType
-> IO Pixbuf
pixbufScaleSimple pb width height interp =
wrapNewGObject mkPixbuf $ liftM castPtr $
(\(Pixbuf arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->gdk_pixbuf_scale_simple argPtr1 arg2 arg3 arg4) (toPixbuf pb)
(fromIntegral width) (fromIntegral height)
(fromIntegral $ fromEnum interp)
pixbufScale ::
Pixbuf
-> Pixbuf
-> Int
-> Int
-> Int
-> Int
-> Double
-> Double
-> Double
-> Double
-> InterpType
-> IO ()
pixbufScale src dest destX destY destWidth destHeight offsetX offsetY
scaleX scaleY interp =
(\(Pixbuf arg1) (Pixbuf arg2) arg3 arg4 arg5 arg6 arg7 arg8 arg9 arg10 arg11 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gdk_pixbuf_scale argPtr1 argPtr2 arg3 arg4 arg5 arg6 arg7 arg8 arg9 arg10 arg11) src dest
(fromIntegral destX) (fromIntegral destY)
(fromIntegral destWidth) (fromIntegral destHeight)
(realToFrac offsetX) (realToFrac offsetY)
(realToFrac scaleX) (realToFrac scaleY)
((fromIntegral . fromEnum) interp)
pixbufComposite ::
Pixbuf
-> Pixbuf
-> Int
-> Int
-> Int
-> Int
-> Double
-> Double
-> Double
-> Double
-> InterpType
-> Word8
-> IO ()
pixbufComposite src dest destX destY destWidth destHeight
offsetX offsetY scaleX scaleY interp alpha =
(\(Pixbuf arg1) (Pixbuf arg2) arg3 arg4 arg5 arg6 arg7 arg8 arg9 arg10 arg11 arg12 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gdk_pixbuf_composite argPtr1 argPtr2 arg3 arg4 arg5 arg6 arg7 arg8 arg9 arg10 arg11 arg12) src dest
(fromIntegral destX) (fromIntegral destY) (fromIntegral destWidth)
(fromIntegral destHeight) (realToFrac offsetX) (realToFrac offsetY)
(realToFrac scaleX) (realToFrac scaleY)
((fromIntegral . fromEnum) interp) (fromIntegral alpha)
pixbufFlipHorizontally :: Pixbuf -> IO Pixbuf
pixbufFlipHorizontally self =
wrapNewGObject mkPixbuf $
(\(Pixbuf arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gdk_pixbuf_flip argPtr1 arg2)
self
(fromBool True)
pixbufFlipHorazontally = pixbufFlipHorizontally
pixbufFlipVertically :: Pixbuf -> IO Pixbuf
pixbufFlipVertically self =
wrapNewGObject mkPixbuf $
(\(Pixbuf arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gdk_pixbuf_flip argPtr1 arg2)
self
(fromBool False)
pixbufRotateSimple :: Pixbuf -> PixbufRotation -> IO Pixbuf
pixbufRotateSimple self angle =
wrapNewGObject mkPixbuf $
(\(Pixbuf arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gdk_pixbuf_rotate_simple argPtr1 arg2)
self
((fromIntegral . fromEnum) angle)
data PixbufRotation = PixbufRotateNone
| PixbufRotateCounterclockwise
| PixbufRotateUpsidedown
| PixbufRotateClockwise
instance Enum PixbufRotation where
fromEnum PixbufRotateNone = 0
fromEnum PixbufRotateCounterclockwise = 90
fromEnum PixbufRotateUpsidedown = 180
fromEnum PixbufRotateClockwise = 270
toEnum 0 = PixbufRotateNone
toEnum 90 = PixbufRotateCounterclockwise
toEnum 180 = PixbufRotateUpsidedown
toEnum 270 = PixbufRotateClockwise
toEnum unmatched = error ("PixbufRotation.toEnum: Cannot match " ++ show unmatched)
succ PixbufRotateNone = PixbufRotateCounterclockwise
succ PixbufRotateCounterclockwise = PixbufRotateUpsidedown
succ PixbufRotateUpsidedown = PixbufRotateClockwise
succ _ = undefined
pred PixbufRotateCounterclockwise = PixbufRotateNone
pred PixbufRotateUpsidedown = PixbufRotateCounterclockwise
pred PixbufRotateClockwise = PixbufRotateUpsidedown
pred _ = undefined
enumFromTo x y | fromEnum x == fromEnum y = [ y ]
| otherwise = x : enumFromTo (succ x) y
enumFrom x = enumFromTo x PixbufRotateClockwise
enumFromThen _ _ = error "Enum PixbufRotation: enumFromThen not implemented"
enumFromThenTo _ _ _ = error "Enum PixbufRotation: enumFromThenTo not implemented"
pixbufAddAlpha :: Pixbuf -> Maybe (Word8, Word8, Word8) -> IO Pixbuf
pixbufAddAlpha pb Nothing = wrapNewGObject mkPixbuf $
(\(Pixbuf arg1) arg2 arg3 arg4 arg5 -> withForeignPtr arg1 $ \argPtr1 ->gdk_pixbuf_add_alpha argPtr1 arg2 arg3 arg4 arg5) pb (fromBool False) 0 0 0
pixbufAddAlpha pb (Just (r,g,b)) = wrapNewGObject mkPixbuf $
(\(Pixbuf arg1) arg2 arg3 arg4 arg5 -> withForeignPtr arg1 $ \argPtr1 ->gdk_pixbuf_add_alpha argPtr1 arg2 arg3 arg4 arg5) pb (fromBool True)
(fromIntegral r) (fromIntegral g) (fromIntegral b)
pixbufCopyArea ::
Pixbuf
-> Int
-> Int
-> Int
-> Int
-> Pixbuf
-> Int
-> Int
-> IO ()
pixbufCopyArea src srcX srcY srcWidth srcHeight dest destX destY =
(\(Pixbuf arg1) arg2 arg3 arg4 arg5 (Pixbuf arg6) arg7 arg8 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg6 $ \argPtr6 ->gdk_pixbuf_copy_area argPtr1 arg2 arg3 arg4 arg5 argPtr6 arg7 arg8) src
(fromIntegral srcX) (fromIntegral srcY)
(fromIntegral srcWidth) (fromIntegral srcHeight)
dest (fromIntegral destX) (fromIntegral destY)
pixbufFill :: Pixbuf -> Word8 -> Word8 -> Word8 -> Word8 -> IO ()
pixbufFill pb red green blue alpha = (\(Pixbuf arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gdk_pixbuf_fill argPtr1 arg2) pb
((fromIntegral red) `shiftL` 24 .|.
(fromIntegral green) `shiftL` 16 .|.
(fromIntegral blue) `shiftL` 8 .|.
(fromIntegral alpha))
pixbufGetFromDrawable :: DrawableClass d => d -> Rectangle -> IO (Maybe Pixbuf)
pixbufGetFromDrawable d (Rectangle x y width height) =
maybeNull (wrapNewGObject mkPixbuf) $
(\(Pixbuf arg1) (Drawable arg2) (Colormap arg3) arg4 arg5 arg6 arg7 arg8 arg9 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->withForeignPtr arg3 $ \argPtr3 ->gdk_pixbuf_get_from_drawable argPtr1 argPtr2 argPtr3 arg4 arg5 arg6 arg7 arg8 arg9)
(Pixbuf nullForeignPtr) (toDrawable d) (Colormap nullForeignPtr)
(fromIntegral x) (fromIntegral y) 0 0
(fromIntegral width) (fromIntegral height)
pixbufRenderThresholdAlpha ::
Pixbuf
-> Bitmap
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> IO ()
pixbufRenderThresholdAlpha src dest srcX srcY destX destY w h at =
withForeignPtr (unPixmap dest) $ \destPtr ->
(\(Pixbuf arg1) arg2 arg3 arg4 arg5 arg6 arg7 arg8 arg9 -> withForeignPtr arg1 $ \argPtr1 ->gdk_pixbuf_render_threshold_alpha argPtr1 arg2 arg3 arg4 arg5 arg6 arg7 arg8 arg9) src
(castPtr destPtr)
(fromIntegral srcX)
(fromIntegral srcY)
(fromIntegral destX)
(fromIntegral destY)
(fromIntegral w)
(fromIntegral h)
(fromIntegral at)
pixbufRenderPixmapAndMaskForColormap ::
Pixbuf
-> Colormap
-> Int
-> IO (Pixmap, Maybe Bitmap)
pixbufRenderPixmapAndMaskForColormap pixbuf colormap threshold =
alloca $ \pmRetPtr ->
alloca $ \bmRetPtr -> do
(\(Pixbuf arg1) (Colormap arg2) arg3 arg4 arg5 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gdk_pixbuf_render_pixmap_and_mask_for_colormap argPtr1 argPtr2 arg3 arg4 arg5) pixbuf
colormap
(castPtr pmRetPtr)
(castPtr bmRetPtr)
(fromIntegral threshold)
pm <- wrapNewGObject mkPixmap (peek pmRetPtr :: IO (Ptr Pixmap))
bm <- maybeNull (wrapNewGObject mkPixmap) (peek bmRetPtr :: IO (Ptr Bitmap))
return (pm, bm)
foreign import ccall unsafe "gdk_pixbuf_get_colorspace"
gdk_pixbuf_get_colorspace :: ((Ptr Pixbuf) -> (IO CInt))
foreign import ccall unsafe "gdk_pixbuf_get_n_channels"
gdk_pixbuf_get_n_channels :: ((Ptr Pixbuf) -> (IO CInt))
foreign import ccall unsafe "gdk_pixbuf_get_has_alpha"
gdk_pixbuf_get_has_alpha :: ((Ptr Pixbuf) -> (IO CInt))
foreign import ccall unsafe "gdk_pixbuf_get_bits_per_sample"
gdk_pixbuf_get_bits_per_sample :: ((Ptr Pixbuf) -> (IO CInt))
foreign import ccall unsafe "gdk_pixbuf_get_pixels"
gdk_pixbuf_get_pixels :: ((Ptr Pixbuf) -> (IO (Ptr CUChar)))
foreign import ccall unsafe "gdk_pixbuf_get_width"
gdk_pixbuf_get_width :: ((Ptr Pixbuf) -> (IO CInt))
foreign import ccall unsafe "gdk_pixbuf_get_height"
gdk_pixbuf_get_height :: ((Ptr Pixbuf) -> (IO CInt))
foreign import ccall unsafe "gdk_pixbuf_get_rowstride"
gdk_pixbuf_get_rowstride :: ((Ptr Pixbuf) -> (IO CInt))
foreign import ccall unsafe "gdk_pixbuf_get_option"
gdk_pixbuf_get_option :: ((Ptr Pixbuf) -> ((Ptr CChar) -> (IO (Ptr CChar))))
foreign import ccall unsafe "gdk_pixbuf_error_quark"
gdk_pixbuf_error_quark :: CUInt
foreign import ccall unsafe "gdk_pixbuf_new_from_file"
gdk_pixbuf_new_from_file :: ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO (Ptr Pixbuf))))
foreign import ccall safe "gdk_pixbuf_new_from_file_at_size"
gdk_pixbuf_new_from_file_at_size :: ((Ptr CChar) -> (CInt -> (CInt -> ((Ptr (Ptr ())) -> (IO (Ptr Pixbuf))))))
foreign import ccall safe "gdk_pixbuf_new_from_file_at_scale"
gdk_pixbuf_new_from_file_at_scale :: ((Ptr CChar) -> (CInt -> (CInt -> (CInt -> ((Ptr (Ptr ())) -> (IO (Ptr Pixbuf)))))))
foreign import ccall unsafe "gdk_pixbuf_savev"
gdk_pixbuf_savev :: ((Ptr Pixbuf) -> ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr (Ptr CChar)) -> ((Ptr (Ptr CChar)) -> ((Ptr (Ptr ())) -> (IO CInt)))))))
foreign import ccall safe "gdk_pixbuf_new"
gdk_pixbuf_new :: (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (IO (Ptr Pixbuf)))))))
foreign import ccall safe "gdk_pixbuf_new_from_data"
gdk_pixbuf_new_from_data :: ((Ptr CUChar) -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> ((FunPtr ((Ptr CUChar) -> ((Ptr ()) -> (IO ())))) -> ((Ptr ()) -> (IO (Ptr Pixbuf)))))))))))
foreign import ccall safe "gdk_pixbuf_new_from_xpm_data"
gdk_pixbuf_new_from_xpm_data :: ((Ptr (Ptr CChar)) -> (IO (Ptr Pixbuf)))
foreign import ccall unsafe "gdk_pixbuf_new_from_inline"
gdk_pixbuf_new_from_inline :: (CInt -> ((Ptr CUChar) -> (CInt -> ((Ptr (Ptr ())) -> (IO (Ptr Pixbuf))))))
foreign import ccall unsafe "gdk_pixbuf_new_subpixbuf"
gdk_pixbuf_new_subpixbuf :: ((Ptr Pixbuf) -> (CInt -> (CInt -> (CInt -> (CInt -> (IO (Ptr Pixbuf)))))))
foreign import ccall unsafe "gdk_pixbuf_copy"
gdk_pixbuf_copy :: ((Ptr Pixbuf) -> (IO (Ptr Pixbuf)))
foreign import ccall safe "gdk_pixbuf_scale_simple"
gdk_pixbuf_scale_simple :: ((Ptr Pixbuf) -> (CInt -> (CInt -> (CInt -> (IO (Ptr Pixbuf))))))
foreign import ccall unsafe "gdk_pixbuf_scale"
gdk_pixbuf_scale :: ((Ptr Pixbuf) -> ((Ptr Pixbuf) -> (CInt -> (CInt -> (CInt -> (CInt -> (CDouble -> (CDouble -> (CDouble -> (CDouble -> (CInt -> (IO ()))))))))))))
foreign import ccall unsafe "gdk_pixbuf_composite"
gdk_pixbuf_composite :: ((Ptr Pixbuf) -> ((Ptr Pixbuf) -> (CInt -> (CInt -> (CInt -> (CInt -> (CDouble -> (CDouble -> (CDouble -> (CDouble -> (CInt -> (CInt -> (IO ())))))))))))))
foreign import ccall safe "gdk_pixbuf_flip"
gdk_pixbuf_flip :: ((Ptr Pixbuf) -> (CInt -> (IO (Ptr Pixbuf))))
foreign import ccall safe "gdk_pixbuf_rotate_simple"
gdk_pixbuf_rotate_simple :: ((Ptr Pixbuf) -> (CInt -> (IO (Ptr Pixbuf))))
foreign import ccall unsafe "gdk_pixbuf_add_alpha"
gdk_pixbuf_add_alpha :: ((Ptr Pixbuf) -> (CInt -> (CUChar -> (CUChar -> (CUChar -> (IO (Ptr Pixbuf)))))))
foreign import ccall unsafe "gdk_pixbuf_copy_area"
gdk_pixbuf_copy_area :: ((Ptr Pixbuf) -> (CInt -> (CInt -> (CInt -> (CInt -> ((Ptr Pixbuf) -> (CInt -> (CInt -> (IO ())))))))))
foreign import ccall unsafe "gdk_pixbuf_fill"
gdk_pixbuf_fill :: ((Ptr Pixbuf) -> (CUInt -> (IO ())))
foreign import ccall unsafe "gdk_pixbuf_get_from_drawable"
gdk_pixbuf_get_from_drawable :: ((Ptr Pixbuf) -> ((Ptr Drawable) -> ((Ptr Colormap) -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (IO (Ptr Pixbuf)))))))))))
foreign import ccall unsafe "gdk_pixbuf_render_threshold_alpha"
gdk_pixbuf_render_threshold_alpha :: ((Ptr Pixbuf) -> ((Ptr ()) -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (CInt -> (IO ()))))))))))
foreign import ccall unsafe "gdk_pixbuf_render_pixmap_and_mask_for_colormap"
gdk_pixbuf_render_pixmap_and_mask_for_colormap :: ((Ptr Pixbuf) -> ((Ptr Colormap) -> ((Ptr Pixmap) -> ((Ptr (Ptr ())) -> (CInt -> (IO ()))))))