{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A pixel buffer.
-- 
-- @GdkPixbuf@ contains information about an image\'s pixel data,
-- its color space, bits per sample, width and height, and the
-- rowstride (the number of bytes between the start of one row
-- and the start of the next).
-- 
-- == Creating new @GdkPixbuf@
-- 
-- The most basic way to create a pixbuf is to wrap an existing pixel
-- buffer with a t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf' instance. You can use the
-- [@ctor\@GdkPixbuf.Pixbuf.new_from_data@] function to do this.
-- 
-- Every time you create a new @GdkPixbuf@ instance for some data, you
-- will need to specify the destroy notification function that will be
-- called when the data buffer needs to be freed; this will happen when
-- a @GdkPixbuf@ is finalized by the reference counting functions. If
-- you have a chunk of static data compiled into your application, you
-- can pass in @NULL@ as the destroy notification function so that the
-- data will not be freed.
-- 
-- The [@ctor\@GdkPixbuf.Pixbuf.new@] constructor function can be used
-- as a convenience to create a pixbuf with an empty buffer; this is
-- equivalent to allocating a data buffer using @malloc()@ and then
-- wrapping it with @gdk_pixbuf_new_from_data()@. The @gdk_pixbuf_new()@
-- function will compute an optimal rowstride so that rendering can be
-- performed with an efficient algorithm.
-- 
-- As a special case, you can use the [@ctor\@GdkPixbuf.Pixbuf.new_from_xpm_data@]
-- function to create a pixbuf from inline XPM image data.
-- 
-- You can also copy an existing pixbuf with the [method/@pixbuf@/.copy]
-- function. This is not the same as just acquiring a reference to
-- the old pixbuf instance: the copy function will actually duplicate
-- the pixel data in memory and create a new [class/@pixbuf@/] instance
-- for it.
-- 
-- == Reference counting
-- 
-- @GdkPixbuf@ structures are reference counted. This means that an
-- application can share a single pixbuf among many parts of the
-- code. When a piece of the program needs to use a pixbuf, it should
-- acquire a reference to it by calling @g_object_ref()@; when it no
-- longer needs the pixbuf, it should release the reference it acquired
-- by calling @g_object_unref()@. The resources associated with a
-- @GdkPixbuf@ will be freed when its reference count drops to zero.
-- Newly-created @GdkPixbuf@ instances start with a reference count
-- of one.
-- 
-- == Image Data
-- 
-- Image data in a pixbuf is stored in memory in an uncompressed,
-- packed format. Rows in the image are stored top to bottom, and
-- in each row pixels are stored from left to right.
-- 
-- There may be padding at the end of a row.
-- 
-- The \"rowstride\" value of a pixbuf, as returned by [@method\@GdkPixbuf.Pixbuf.get_rowstride@],
-- indicates the number of bytes between rows.
-- 
-- **NOTE**: If you are copying raw pixbuf data with @memcpy()@ note that the
-- last row in the pixbuf may not be as wide as the full rowstride, but rather
-- just as wide as the pixel data needs to be; that is: it is unsafe to do
-- @memcpy (dest, pixels, rowstride * height)@ to copy a whole pixbuf. Use
-- 'GI.GdkPixbuf.Objects.Pixbuf.pixbufCopy' instead, or compute the width in bytes of the
-- last row as:
-- 
-- 
-- === /c code/
-- >last_row = width * ((n_channels * bits_per_sample + 7) / 8);
-- 
-- 
-- The same rule applies when iterating over each row of a @GdkPixbuf@ pixels
-- array.
-- 
-- The following code illustrates a simple @put_pixel()@
-- function for RGB pixbufs with 8 bits per channel with an alpha
-- channel.
-- 
-- 
-- === /c code/
-- >static void
-- >put_pixel (GdkPixbuf *pixbuf,
-- >           int x,
-- >	   int y,
-- >	   guchar red,
-- >	   guchar green,
-- >	   guchar blue,
-- >	   guchar alpha)
-- >{
-- >  int n_channels = gdk_pixbuf_get_n_channels (pixbuf);
-- >
-- >  // Ensure that the pixbuf is valid
-- >  g_assert (gdk_pixbuf_get_colorspace (pixbuf) == GDK_COLORSPACE_RGB);
-- >  g_assert (gdk_pixbuf_get_bits_per_sample (pixbuf) == 8);
-- >  g_assert (gdk_pixbuf_get_has_alpha (pixbuf));
-- >  g_assert (n_channels == 4);
-- >
-- >  int width = gdk_pixbuf_get_width (pixbuf);
-- >  int height = gdk_pixbuf_get_height (pixbuf);
-- >
-- >  // Ensure that the coordinates are in a valid range
-- >  g_assert (x >= 0 && x < width);
-- >  g_assert (y >= 0 && y < height);
-- >
-- >  int rowstride = gdk_pixbuf_get_rowstride (pixbuf);
-- >
-- >  // The pixel buffer in the GdkPixbuf instance
-- >  guchar *pixels = gdk_pixbuf_get_pixels (pixbuf);
-- >
-- >  // The pixel we wish to modify
-- >  guchar *p = pixels + y * rowstride + x * n_channels;
-- >  p[0] = red;
-- >  p[1] = green;
-- >  p[2] = blue;
-- >  p[3] = alpha;
-- >}
-- 
-- 
-- == Loading images
-- 
-- The @GdkPixBuf@ class provides a simple mechanism for loading
-- an image from a file in synchronous and asynchronous fashion.
-- 
-- For GUI applications, it is recommended to use the asynchronous
-- stream API to avoid blocking the control flow of the application.
-- 
-- Additionally, @GdkPixbuf@ provides the [class/@gdkPixbuf@/.PixbufLoader@]
-- API for progressive image loading.
-- 
-- ## Saving images
-- 
-- The @GdkPixbuf@ class provides methods for saving image data in
-- a number of file formats. The formatted data can be written to a
-- file or to a memory buffer. @GdkPixbuf\` can also call a user-defined
-- callback on the data, which allows to e.g. write the image
-- to a socket or store it in a database.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.GdkPixbuf.Objects.Pixbuf
    ( 
#if defined(ENABLE_OVERLOADING)
    PixbufGetOptionsMethodInfo              ,
#endif

-- * Exported types
    Pixbuf(..)                              ,
    IsPixbuf                                ,
    toPixbuf                                ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [addAlpha]("GI.GdkPixbuf.Objects.Pixbuf#g:method:addAlpha"), [applyEmbeddedOrientation]("GI.GdkPixbuf.Objects.Pixbuf#g:method:applyEmbeddedOrientation"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [composite]("GI.GdkPixbuf.Objects.Pixbuf#g:method:composite"), [compositeColor]("GI.GdkPixbuf.Objects.Pixbuf#g:method:compositeColor"), [compositeColorSimple]("GI.GdkPixbuf.Objects.Pixbuf#g:method:compositeColorSimple"), [copy]("GI.GdkPixbuf.Objects.Pixbuf#g:method:copy"), [copyArea]("GI.GdkPixbuf.Objects.Pixbuf#g:method:copyArea"), [copyOptions]("GI.GdkPixbuf.Objects.Pixbuf#g:method:copyOptions"), [equal]("GI.Gio.Interfaces.Icon#g:method:equal"), [fill]("GI.GdkPixbuf.Objects.Pixbuf#g:method:fill"), [flip]("GI.GdkPixbuf.Objects.Pixbuf#g:method:flip"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [load]("GI.Gio.Interfaces.LoadableIcon#g:method:load"), [loadAsync]("GI.Gio.Interfaces.LoadableIcon#g:method:loadAsync"), [loadFinish]("GI.Gio.Interfaces.LoadableIcon#g:method:loadFinish"), [newSubpixbuf]("GI.GdkPixbuf.Objects.Pixbuf#g:method:newSubpixbuf"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [readPixelBytes]("GI.GdkPixbuf.Objects.Pixbuf#g:method:readPixelBytes"), [readPixels]("GI.GdkPixbuf.Objects.Pixbuf#g:method:readPixels"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [removeOption]("GI.GdkPixbuf.Objects.Pixbuf#g:method:removeOption"), [rotateSimple]("GI.GdkPixbuf.Objects.Pixbuf#g:method:rotateSimple"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [saturateAndPixelate]("GI.GdkPixbuf.Objects.Pixbuf#g:method:saturateAndPixelate"), [saveToBufferv]("GI.GdkPixbuf.Objects.Pixbuf#g:method:saveToBufferv"), [saveToCallbackv]("GI.GdkPixbuf.Objects.Pixbuf#g:method:saveToCallbackv"), [saveToStreamv]("GI.GdkPixbuf.Objects.Pixbuf#g:method:saveToStreamv"), [saveToStreamvAsync]("GI.GdkPixbuf.Objects.Pixbuf#g:method:saveToStreamvAsync"), [savev]("GI.GdkPixbuf.Objects.Pixbuf#g:method:savev"), [scale]("GI.GdkPixbuf.Objects.Pixbuf#g:method:scale"), [scaleSimple]("GI.GdkPixbuf.Objects.Pixbuf#g:method:scaleSimple"), [serialize]("GI.Gio.Interfaces.Icon#g:method:serialize"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [toString]("GI.Gio.Interfaces.Icon#g:method:toString"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getBitsPerSample]("GI.GdkPixbuf.Objects.Pixbuf#g:method:getBitsPerSample"), [getByteLength]("GI.GdkPixbuf.Objects.Pixbuf#g:method:getByteLength"), [getColorspace]("GI.GdkPixbuf.Objects.Pixbuf#g:method:getColorspace"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getHasAlpha]("GI.GdkPixbuf.Objects.Pixbuf#g:method:getHasAlpha"), [getHeight]("GI.GdkPixbuf.Objects.Pixbuf#g:method:getHeight"), [getNChannels]("GI.GdkPixbuf.Objects.Pixbuf#g:method:getNChannels"), [getOption]("GI.GdkPixbuf.Objects.Pixbuf#g:method:getOption"), [getOptions]("GI.GdkPixbuf.Objects.Pixbuf#g:method:getOptions"), [getPixels]("GI.GdkPixbuf.Objects.Pixbuf#g:method:getPixels"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRowstride]("GI.GdkPixbuf.Objects.Pixbuf#g:method:getRowstride"), [getWidth]("GI.GdkPixbuf.Objects.Pixbuf#g:method:getWidth").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setOption]("GI.GdkPixbuf.Objects.Pixbuf#g:method:setOption"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolvePixbufMethod                     ,
#endif

-- ** addAlpha #method:addAlpha#

#if defined(ENABLE_OVERLOADING)
    PixbufAddAlphaMethodInfo                ,
#endif
    pixbufAddAlpha                          ,


-- ** applyEmbeddedOrientation #method:applyEmbeddedOrientation#

#if defined(ENABLE_OVERLOADING)
    PixbufApplyEmbeddedOrientationMethodInfo,
#endif
    pixbufApplyEmbeddedOrientation          ,


-- ** calculateRowstride #method:calculateRowstride#

    pixbufCalculateRowstride                ,


-- ** composite #method:composite#

#if defined(ENABLE_OVERLOADING)
    PixbufCompositeMethodInfo               ,
#endif
    pixbufComposite                         ,


-- ** compositeColor #method:compositeColor#

#if defined(ENABLE_OVERLOADING)
    PixbufCompositeColorMethodInfo          ,
#endif
    pixbufCompositeColor                    ,


-- ** compositeColorSimple #method:compositeColorSimple#

#if defined(ENABLE_OVERLOADING)
    PixbufCompositeColorSimpleMethodInfo    ,
#endif
    pixbufCompositeColorSimple              ,


-- ** copy #method:copy#

#if defined(ENABLE_OVERLOADING)
    PixbufCopyMethodInfo                    ,
#endif
    pixbufCopy                              ,


-- ** copyArea #method:copyArea#

#if defined(ENABLE_OVERLOADING)
    PixbufCopyAreaMethodInfo                ,
#endif
    pixbufCopyArea                          ,


-- ** copyOptions #method:copyOptions#

#if defined(ENABLE_OVERLOADING)
    PixbufCopyOptionsMethodInfo             ,
#endif
    pixbufCopyOptions                       ,


-- ** fill #method:fill#

#if defined(ENABLE_OVERLOADING)
    PixbufFillMethodInfo                    ,
#endif
    pixbufFill                              ,


-- ** flip #method:flip#

#if defined(ENABLE_OVERLOADING)
    PixbufFlipMethodInfo                    ,
#endif
    pixbufFlip                              ,


-- ** getBitsPerSample #method:getBitsPerSample#

#if defined(ENABLE_OVERLOADING)
    PixbufGetBitsPerSampleMethodInfo        ,
#endif
    pixbufGetBitsPerSample                  ,


-- ** getByteLength #method:getByteLength#

#if defined(ENABLE_OVERLOADING)
    PixbufGetByteLengthMethodInfo           ,
#endif
    pixbufGetByteLength                     ,


-- ** getColorspace #method:getColorspace#

#if defined(ENABLE_OVERLOADING)
    PixbufGetColorspaceMethodInfo           ,
#endif
    pixbufGetColorspace                     ,


-- ** getFileInfo #method:getFileInfo#

    pixbufGetFileInfo                       ,


-- ** getFileInfoAsync #method:getFileInfoAsync#

    pixbufGetFileInfoAsync                  ,


-- ** getFileInfoFinish #method:getFileInfoFinish#

    pixbufGetFileInfoFinish                 ,


-- ** getFormats #method:getFormats#

    pixbufGetFormats                        ,


-- ** getHasAlpha #method:getHasAlpha#

#if defined(ENABLE_OVERLOADING)
    PixbufGetHasAlphaMethodInfo             ,
#endif
    pixbufGetHasAlpha                       ,


-- ** getHeight #method:getHeight#

#if defined(ENABLE_OVERLOADING)
    PixbufGetHeightMethodInfo               ,
#endif
    pixbufGetHeight                         ,


-- ** getNChannels #method:getNChannels#

#if defined(ENABLE_OVERLOADING)
    PixbufGetNChannelsMethodInfo            ,
#endif
    pixbufGetNChannels                      ,


-- ** getOption #method:getOption#

#if defined(ENABLE_OVERLOADING)
    PixbufGetOptionMethodInfo               ,
#endif
    pixbufGetOption                         ,


-- ** getPixels #method:getPixels#

#if defined(ENABLE_OVERLOADING)
    PixbufGetPixelsMethodInfo               ,
#endif
    pixbufGetPixels                         ,


-- ** getRowstride #method:getRowstride#

#if defined(ENABLE_OVERLOADING)
    PixbufGetRowstrideMethodInfo            ,
#endif
    pixbufGetRowstride                      ,


-- ** getWidth #method:getWidth#

#if defined(ENABLE_OVERLOADING)
    PixbufGetWidthMethodInfo                ,
#endif
    pixbufGetWidth                          ,


-- ** initModules #method:initModules#

    pixbufInitModules                       ,


-- ** new #method:new#

    pixbufNew                               ,


-- ** newFromBytes #method:newFromBytes#

    pixbufNewFromBytes                      ,


-- ** newFromData #method:newFromData#

    pixbufNewFromData                       ,


-- ** newFromFile #method:newFromFile#

    pixbufNewFromFile                       ,


-- ** newFromFileAtScale #method:newFromFileAtScale#

    pixbufNewFromFileAtScale                ,


-- ** newFromFileAtSize #method:newFromFileAtSize#

    pixbufNewFromFileAtSize                 ,


-- ** newFromInline #method:newFromInline#

    pixbufNewFromInline                     ,


-- ** newFromResource #method:newFromResource#

    pixbufNewFromResource                   ,


-- ** newFromResourceAtScale #method:newFromResourceAtScale#

    pixbufNewFromResourceAtScale            ,


-- ** newFromStream #method:newFromStream#

    pixbufNewFromStream                     ,


-- ** newFromStreamAsync #method:newFromStreamAsync#

    pixbufNewFromStreamAsync                ,


-- ** newFromStreamAtScale #method:newFromStreamAtScale#

    pixbufNewFromStreamAtScale              ,


-- ** newFromStreamAtScaleAsync #method:newFromStreamAtScaleAsync#

    pixbufNewFromStreamAtScaleAsync         ,


-- ** newFromStreamFinish #method:newFromStreamFinish#

    pixbufNewFromStreamFinish               ,


-- ** newFromXpmData #method:newFromXpmData#

    pixbufNewFromXpmData                    ,


-- ** newSubpixbuf #method:newSubpixbuf#

#if defined(ENABLE_OVERLOADING)
    PixbufNewSubpixbufMethodInfo            ,
#endif
    pixbufNewSubpixbuf                      ,


-- ** readPixelBytes #method:readPixelBytes#

#if defined(ENABLE_OVERLOADING)
    PixbufReadPixelBytesMethodInfo          ,
#endif
    pixbufReadPixelBytes                    ,


-- ** readPixels #method:readPixels#

#if defined(ENABLE_OVERLOADING)
    PixbufReadPixelsMethodInfo              ,
#endif
    pixbufReadPixels                        ,


-- ** removeOption #method:removeOption#

#if defined(ENABLE_OVERLOADING)
    PixbufRemoveOptionMethodInfo            ,
#endif
    pixbufRemoveOption                      ,


-- ** rotateSimple #method:rotateSimple#

#if defined(ENABLE_OVERLOADING)
    PixbufRotateSimpleMethodInfo            ,
#endif
    pixbufRotateSimple                      ,


-- ** saturateAndPixelate #method:saturateAndPixelate#

#if defined(ENABLE_OVERLOADING)
    PixbufSaturateAndPixelateMethodInfo     ,
#endif
    pixbufSaturateAndPixelate               ,


-- ** saveToBufferv #method:saveToBufferv#

#if defined(ENABLE_OVERLOADING)
    PixbufSaveToBuffervMethodInfo           ,
#endif
    pixbufSaveToBufferv                     ,


-- ** saveToCallbackv #method:saveToCallbackv#

#if defined(ENABLE_OVERLOADING)
    PixbufSaveToCallbackvMethodInfo         ,
#endif
    pixbufSaveToCallbackv                   ,


-- ** saveToStreamFinish #method:saveToStreamFinish#

    pixbufSaveToStreamFinish                ,


-- ** saveToStreamv #method:saveToStreamv#

#if defined(ENABLE_OVERLOADING)
    PixbufSaveToStreamvMethodInfo           ,
#endif
    pixbufSaveToStreamv                     ,


-- ** saveToStreamvAsync #method:saveToStreamvAsync#

#if defined(ENABLE_OVERLOADING)
    PixbufSaveToStreamvAsyncMethodInfo      ,
#endif
    pixbufSaveToStreamvAsync                ,


-- ** savev #method:savev#

#if defined(ENABLE_OVERLOADING)
    PixbufSavevMethodInfo                   ,
#endif
    pixbufSavev                             ,


-- ** scale #method:scale#

#if defined(ENABLE_OVERLOADING)
    PixbufScaleMethodInfo                   ,
#endif
    pixbufScale                             ,


-- ** scaleSimple #method:scaleSimple#

#if defined(ENABLE_OVERLOADING)
    PixbufScaleSimpleMethodInfo             ,
#endif
    pixbufScaleSimple                       ,


-- ** setOption #method:setOption#

#if defined(ENABLE_OVERLOADING)
    PixbufSetOptionMethodInfo               ,
#endif
    pixbufSetOption                         ,




 -- * Properties


-- ** bitsPerSample #attr:bitsPerSample#
-- | The number of bits per sample.
-- 
-- Currently only 8 bit per sample are supported.

#if defined(ENABLE_OVERLOADING)
    PixbufBitsPerSamplePropertyInfo         ,
#endif
    constructPixbufBitsPerSample            ,
    getPixbufBitsPerSample                  ,
#if defined(ENABLE_OVERLOADING)
    pixbufBitsPerSample                     ,
#endif


-- ** colorspace #attr:colorspace#
-- | The color space of the pixbuf.
-- 
-- Currently, only @GDK_COLORSPACE_RGB@ is supported.

#if defined(ENABLE_OVERLOADING)
    PixbufColorspacePropertyInfo            ,
#endif
    constructPixbufColorspace               ,
    getPixbufColorspace                     ,
#if defined(ENABLE_OVERLOADING)
    pixbufColorspace                        ,
#endif


-- ** hasAlpha #attr:hasAlpha#
-- | Whether the pixbuf has an alpha channel.

#if defined(ENABLE_OVERLOADING)
    PixbufHasAlphaPropertyInfo              ,
#endif
    constructPixbufHasAlpha                 ,
    getPixbufHasAlpha                       ,
#if defined(ENABLE_OVERLOADING)
    pixbufHasAlpha                          ,
#endif


-- ** height #attr:height#
-- | The number of rows of the pixbuf.

#if defined(ENABLE_OVERLOADING)
    PixbufHeightPropertyInfo                ,
#endif
    constructPixbufHeight                   ,
    getPixbufHeight                         ,
#if defined(ENABLE_OVERLOADING)
    pixbufHeight                            ,
#endif


-- ** nChannels #attr:nChannels#
-- | The number of samples per pixel.
-- 
-- Currently, only 3 or 4 samples per pixel are supported.

#if defined(ENABLE_OVERLOADING)
    PixbufNChannelsPropertyInfo             ,
#endif
    constructPixbufNChannels                ,
    getPixbufNChannels                      ,
#if defined(ENABLE_OVERLOADING)
    pixbufNChannels                         ,
#endif


-- ** pixelBytes #attr:pixelBytes#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    PixbufPixelBytesPropertyInfo            ,
#endif
    constructPixbufPixelBytes               ,
    getPixbufPixelBytes                     ,
#if defined(ENABLE_OVERLOADING)
    pixbufPixelBytes                        ,
#endif


-- ** pixels #attr:pixels#
-- | A pointer to the pixel data of the pixbuf.

#if defined(ENABLE_OVERLOADING)
    PixbufPixelsPropertyInfo                ,
#endif
    constructPixbufPixels                   ,
    getPixbufPixels                         ,
#if defined(ENABLE_OVERLOADING)
    pixbufPixels                            ,
#endif


-- ** rowstride #attr:rowstride#
-- | The number of bytes between the start of a row and
-- the start of the next row.
-- 
-- This number must (obviously) be at least as large as the
-- width of the pixbuf.

#if defined(ENABLE_OVERLOADING)
    PixbufRowstridePropertyInfo             ,
#endif
    constructPixbufRowstride                ,
    getPixbufRowstride                      ,
#if defined(ENABLE_OVERLOADING)
    pixbufRowstride                         ,
#endif


-- ** width #attr:width#
-- | The number of columns of the pixbuf.

#if defined(ENABLE_OVERLOADING)
    PixbufWidthPropertyInfo                 ,
#endif
    constructPixbufWidth                    ,
    getPixbufWidth                          ,
#if defined(ENABLE_OVERLOADING)
    pixbufWidth                             ,
#endif




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.GdkPixbuf.Callbacks as GdkPixbuf.Callbacks
import {-# SOURCE #-} qualified GI.GdkPixbuf.Enums as GdkPixbuf.Enums
import {-# SOURCE #-} qualified GI.GdkPixbuf.Structs.PixbufFormat as GdkPixbuf.PixbufFormat
import qualified GI.Gio.Callbacks as Gio.Callbacks
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gio.Interfaces.LoadableIcon as Gio.LoadableIcon
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import qualified GI.Gio.Objects.InputStream as Gio.InputStream
import qualified GI.Gio.Objects.OutputStream as Gio.OutputStream

-- | Memory-managed wrapper type.
newtype Pixbuf = Pixbuf (SP.ManagedPtr Pixbuf)
    deriving (Pixbuf -> Pixbuf -> Bool
(Pixbuf -> Pixbuf -> Bool)
-> (Pixbuf -> Pixbuf -> Bool) -> Eq Pixbuf
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Pixbuf -> Pixbuf -> Bool
== :: Pixbuf -> Pixbuf -> Bool
$c/= :: Pixbuf -> Pixbuf -> Bool
/= :: Pixbuf -> Pixbuf -> Bool
Eq)

instance SP.ManagedPtrNewtype Pixbuf where
    toManagedPtr :: Pixbuf -> ManagedPtr Pixbuf
toManagedPtr (Pixbuf ManagedPtr Pixbuf
p) = ManagedPtr Pixbuf
p

foreign import ccall "gdk_pixbuf_get_type"
    c_gdk_pixbuf_get_type :: IO B.Types.GType

instance B.Types.TypedObject Pixbuf where
    glibType :: IO GType
glibType = IO GType
c_gdk_pixbuf_get_type

instance B.Types.GObject Pixbuf

-- | Type class for types which can be safely cast to `Pixbuf`, for instance with `toPixbuf`.
class (SP.GObject o, O.IsDescendantOf Pixbuf o) => IsPixbuf o
instance (SP.GObject o, O.IsDescendantOf Pixbuf o) => IsPixbuf o

instance O.HasParentTypes Pixbuf
type instance O.ParentTypes Pixbuf = '[GObject.Object.Object, Gio.Icon.Icon, Gio.LoadableIcon.LoadableIcon]

-- | Cast to `Pixbuf`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toPixbuf :: (MIO.MonadIO m, IsPixbuf o) => o -> m Pixbuf
toPixbuf :: forall (m :: * -> *) o. (MonadIO m, IsPixbuf o) => o -> m Pixbuf
toPixbuf = IO Pixbuf -> m Pixbuf
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Pixbuf -> m Pixbuf) -> (o -> IO Pixbuf) -> o -> m Pixbuf
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Pixbuf -> Pixbuf) -> o -> IO Pixbuf
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Pixbuf -> Pixbuf
Pixbuf

-- | Convert 'Pixbuf' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe Pixbuf) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gdk_pixbuf_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Pixbuf -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Pixbuf
P.Nothing = Ptr GValue -> Ptr Pixbuf -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Pixbuf
forall a. Ptr a
FP.nullPtr :: FP.Ptr Pixbuf)
    gvalueSet_ Ptr GValue
gv (P.Just Pixbuf
obj) = Pixbuf -> (Ptr Pixbuf -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Pixbuf
obj (Ptr GValue -> Ptr Pixbuf -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Pixbuf)
gvalueGet_ Ptr GValue
gv = do
        Ptr Pixbuf
ptr <- Ptr GValue -> IO (Ptr Pixbuf)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Pixbuf)
        if Ptr Pixbuf
ptr Ptr Pixbuf -> Ptr Pixbuf -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Pixbuf
forall a. Ptr a
FP.nullPtr
        then Pixbuf -> Maybe Pixbuf
forall a. a -> Maybe a
P.Just (Pixbuf -> Maybe Pixbuf) -> IO Pixbuf -> IO (Maybe Pixbuf)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Pixbuf -> Pixbuf
Pixbuf Ptr Pixbuf
ptr
        else Maybe Pixbuf -> IO (Maybe Pixbuf)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolvePixbufMethod (t :: Symbol) (o :: *) :: * where
    ResolvePixbufMethod "addAlpha" o = PixbufAddAlphaMethodInfo
    ResolvePixbufMethod "applyEmbeddedOrientation" o = PixbufApplyEmbeddedOrientationMethodInfo
    ResolvePixbufMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolvePixbufMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolvePixbufMethod "composite" o = PixbufCompositeMethodInfo
    ResolvePixbufMethod "compositeColor" o = PixbufCompositeColorMethodInfo
    ResolvePixbufMethod "compositeColorSimple" o = PixbufCompositeColorSimpleMethodInfo
    ResolvePixbufMethod "copy" o = PixbufCopyMethodInfo
    ResolvePixbufMethod "copyArea" o = PixbufCopyAreaMethodInfo
    ResolvePixbufMethod "copyOptions" o = PixbufCopyOptionsMethodInfo
    ResolvePixbufMethod "equal" o = Gio.Icon.IconEqualMethodInfo
    ResolvePixbufMethod "fill" o = PixbufFillMethodInfo
    ResolvePixbufMethod "flip" o = PixbufFlipMethodInfo
    ResolvePixbufMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolvePixbufMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolvePixbufMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolvePixbufMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolvePixbufMethod "load" o = Gio.LoadableIcon.LoadableIconLoadMethodInfo
    ResolvePixbufMethod "loadAsync" o = Gio.LoadableIcon.LoadableIconLoadAsyncMethodInfo
    ResolvePixbufMethod "loadFinish" o = Gio.LoadableIcon.LoadableIconLoadFinishMethodInfo
    ResolvePixbufMethod "newSubpixbuf" o = PixbufNewSubpixbufMethodInfo
    ResolvePixbufMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolvePixbufMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolvePixbufMethod "readPixelBytes" o = PixbufReadPixelBytesMethodInfo
    ResolvePixbufMethod "readPixels" o = PixbufReadPixelsMethodInfo
    ResolvePixbufMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolvePixbufMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolvePixbufMethod "removeOption" o = PixbufRemoveOptionMethodInfo
    ResolvePixbufMethod "rotateSimple" o = PixbufRotateSimpleMethodInfo
    ResolvePixbufMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolvePixbufMethod "saturateAndPixelate" o = PixbufSaturateAndPixelateMethodInfo
    ResolvePixbufMethod "saveToBufferv" o = PixbufSaveToBuffervMethodInfo
    ResolvePixbufMethod "saveToCallbackv" o = PixbufSaveToCallbackvMethodInfo
    ResolvePixbufMethod "saveToStreamv" o = PixbufSaveToStreamvMethodInfo
    ResolvePixbufMethod "saveToStreamvAsync" o = PixbufSaveToStreamvAsyncMethodInfo
    ResolvePixbufMethod "savev" o = PixbufSavevMethodInfo
    ResolvePixbufMethod "scale" o = PixbufScaleMethodInfo
    ResolvePixbufMethod "scaleSimple" o = PixbufScaleSimpleMethodInfo
    ResolvePixbufMethod "serialize" o = Gio.Icon.IconSerializeMethodInfo
    ResolvePixbufMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolvePixbufMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolvePixbufMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolvePixbufMethod "toString" o = Gio.Icon.IconToStringMethodInfo
    ResolvePixbufMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolvePixbufMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolvePixbufMethod "getBitsPerSample" o = PixbufGetBitsPerSampleMethodInfo
    ResolvePixbufMethod "getByteLength" o = PixbufGetByteLengthMethodInfo
    ResolvePixbufMethod "getColorspace" o = PixbufGetColorspaceMethodInfo
    ResolvePixbufMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolvePixbufMethod "getHasAlpha" o = PixbufGetHasAlphaMethodInfo
    ResolvePixbufMethod "getHeight" o = PixbufGetHeightMethodInfo
    ResolvePixbufMethod "getNChannels" o = PixbufGetNChannelsMethodInfo
    ResolvePixbufMethod "getOption" o = PixbufGetOptionMethodInfo
    ResolvePixbufMethod "getOptions" o = PixbufGetOptionsMethodInfo
    ResolvePixbufMethod "getPixels" o = PixbufGetPixelsMethodInfo
    ResolvePixbufMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolvePixbufMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolvePixbufMethod "getRowstride" o = PixbufGetRowstrideMethodInfo
    ResolvePixbufMethod "getWidth" o = PixbufGetWidthMethodInfo
    ResolvePixbufMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolvePixbufMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolvePixbufMethod "setOption" o = PixbufSetOptionMethodInfo
    ResolvePixbufMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolvePixbufMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolvePixbufMethod t Pixbuf, O.OverloadedMethod info Pixbuf p) => OL.IsLabel t (Pixbuf -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolvePixbufMethod t Pixbuf, O.OverloadedMethod info Pixbuf p, R.HasField t Pixbuf p) => R.HasField t Pixbuf p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolvePixbufMethod t Pixbuf, O.OverloadedMethodInfo info Pixbuf) => OL.IsLabel t (O.MethodProxy info Pixbuf) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- VVV Prop "bits-per-sample"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@bits-per-sample@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' pixbuf #bitsPerSample
-- @
getPixbufBitsPerSample :: (MonadIO m, IsPixbuf o) => o -> m Int32
getPixbufBitsPerSample :: forall (m :: * -> *) o. (MonadIO m, IsPixbuf o) => o -> m Int32
getPixbufBitsPerSample o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"bits-per-sample"

-- | Construct a `GValueConstruct` with valid value for the “@bits-per-sample@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPixbufBitsPerSample :: (IsPixbuf o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructPixbufBitsPerSample :: forall o (m :: * -> *).
(IsPixbuf o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructPixbufBitsPerSample Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"bits-per-sample" Int32
val

#if defined(ENABLE_OVERLOADING)
data PixbufBitsPerSamplePropertyInfo
instance AttrInfo PixbufBitsPerSamplePropertyInfo where
    type AttrAllowedOps PixbufBitsPerSamplePropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PixbufBitsPerSamplePropertyInfo = IsPixbuf
    type AttrSetTypeConstraint PixbufBitsPerSamplePropertyInfo = (~) Int32
    type AttrTransferTypeConstraint PixbufBitsPerSamplePropertyInfo = (~) Int32
    type AttrTransferType PixbufBitsPerSamplePropertyInfo = Int32
    type AttrGetType PixbufBitsPerSamplePropertyInfo = Int32
    type AttrLabel PixbufBitsPerSamplePropertyInfo = "bits-per-sample"
    type AttrOrigin PixbufBitsPerSamplePropertyInfo = Pixbuf
    attrGet = getPixbufBitsPerSample
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructPixbufBitsPerSample
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.bitsPerSample"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#g:attr:bitsPerSample"
        })
#endif

-- VVV Prop "colorspace"
   -- Type: TInterface (Name {namespace = "GdkPixbuf", name = "Colorspace"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@colorspace@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' pixbuf #colorspace
-- @
getPixbufColorspace :: (MonadIO m, IsPixbuf o) => o -> m GdkPixbuf.Enums.Colorspace
getPixbufColorspace :: forall (m :: * -> *) o.
(MonadIO m, IsPixbuf o) =>
o -> m Colorspace
getPixbufColorspace o
obj = IO Colorspace -> m Colorspace
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Colorspace -> m Colorspace) -> IO Colorspace -> m Colorspace
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Colorspace
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"colorspace"

-- | Construct a `GValueConstruct` with valid value for the “@colorspace@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPixbufColorspace :: (IsPixbuf o, MIO.MonadIO m) => GdkPixbuf.Enums.Colorspace -> m (GValueConstruct o)
constructPixbufColorspace :: forall o (m :: * -> *).
(IsPixbuf o, MonadIO m) =>
Colorspace -> m (GValueConstruct o)
constructPixbufColorspace Colorspace
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Colorspace -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"colorspace" Colorspace
val

#if defined(ENABLE_OVERLOADING)
data PixbufColorspacePropertyInfo
instance AttrInfo PixbufColorspacePropertyInfo where
    type AttrAllowedOps PixbufColorspacePropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PixbufColorspacePropertyInfo = IsPixbuf
    type AttrSetTypeConstraint PixbufColorspacePropertyInfo = (~) GdkPixbuf.Enums.Colorspace
    type AttrTransferTypeConstraint PixbufColorspacePropertyInfo = (~) GdkPixbuf.Enums.Colorspace
    type AttrTransferType PixbufColorspacePropertyInfo = GdkPixbuf.Enums.Colorspace
    type AttrGetType PixbufColorspacePropertyInfo = GdkPixbuf.Enums.Colorspace
    type AttrLabel PixbufColorspacePropertyInfo = "colorspace"
    type AttrOrigin PixbufColorspacePropertyInfo = Pixbuf
    attrGet = getPixbufColorspace
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructPixbufColorspace
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.colorspace"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#g:attr:colorspace"
        })
#endif

-- VVV Prop "has-alpha"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@has-alpha@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' pixbuf #hasAlpha
-- @
getPixbufHasAlpha :: (MonadIO m, IsPixbuf o) => o -> m Bool
getPixbufHasAlpha :: forall (m :: * -> *) o. (MonadIO m, IsPixbuf o) => o -> m Bool
getPixbufHasAlpha o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"has-alpha"

-- | Construct a `GValueConstruct` with valid value for the “@has-alpha@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPixbufHasAlpha :: (IsPixbuf o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructPixbufHasAlpha :: forall o (m :: * -> *).
(IsPixbuf o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructPixbufHasAlpha Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"has-alpha" Bool
val

#if defined(ENABLE_OVERLOADING)
data PixbufHasAlphaPropertyInfo
instance AttrInfo PixbufHasAlphaPropertyInfo where
    type AttrAllowedOps PixbufHasAlphaPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PixbufHasAlphaPropertyInfo = IsPixbuf
    type AttrSetTypeConstraint PixbufHasAlphaPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint PixbufHasAlphaPropertyInfo = (~) Bool
    type AttrTransferType PixbufHasAlphaPropertyInfo = Bool
    type AttrGetType PixbufHasAlphaPropertyInfo = Bool
    type AttrLabel PixbufHasAlphaPropertyInfo = "has-alpha"
    type AttrOrigin PixbufHasAlphaPropertyInfo = Pixbuf
    attrGet = getPixbufHasAlpha
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructPixbufHasAlpha
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.hasAlpha"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#g:attr:hasAlpha"
        })
#endif

-- VVV Prop "height"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@height@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' pixbuf #height
-- @
getPixbufHeight :: (MonadIO m, IsPixbuf o) => o -> m Int32
getPixbufHeight :: forall (m :: * -> *) o. (MonadIO m, IsPixbuf o) => o -> m Int32
getPixbufHeight o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"height"

-- | Construct a `GValueConstruct` with valid value for the “@height@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPixbufHeight :: (IsPixbuf o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructPixbufHeight :: forall o (m :: * -> *).
(IsPixbuf o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructPixbufHeight Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"height" Int32
val

#if defined(ENABLE_OVERLOADING)
data PixbufHeightPropertyInfo
instance AttrInfo PixbufHeightPropertyInfo where
    type AttrAllowedOps PixbufHeightPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PixbufHeightPropertyInfo = IsPixbuf
    type AttrSetTypeConstraint PixbufHeightPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint PixbufHeightPropertyInfo = (~) Int32
    type AttrTransferType PixbufHeightPropertyInfo = Int32
    type AttrGetType PixbufHeightPropertyInfo = Int32
    type AttrLabel PixbufHeightPropertyInfo = "height"
    type AttrOrigin PixbufHeightPropertyInfo = Pixbuf
    attrGet = getPixbufHeight
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructPixbufHeight
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.height"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#g:attr:height"
        })
#endif

-- VVV Prop "n-channels"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@n-channels@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' pixbuf #nChannels
-- @
getPixbufNChannels :: (MonadIO m, IsPixbuf o) => o -> m Int32
getPixbufNChannels :: forall (m :: * -> *) o. (MonadIO m, IsPixbuf o) => o -> m Int32
getPixbufNChannels o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"n-channels"

-- | Construct a `GValueConstruct` with valid value for the “@n-channels@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPixbufNChannels :: (IsPixbuf o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructPixbufNChannels :: forall o (m :: * -> *).
(IsPixbuf o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructPixbufNChannels Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"n-channels" Int32
val

#if defined(ENABLE_OVERLOADING)
data PixbufNChannelsPropertyInfo
instance AttrInfo PixbufNChannelsPropertyInfo where
    type AttrAllowedOps PixbufNChannelsPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PixbufNChannelsPropertyInfo = IsPixbuf
    type AttrSetTypeConstraint PixbufNChannelsPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint PixbufNChannelsPropertyInfo = (~) Int32
    type AttrTransferType PixbufNChannelsPropertyInfo = Int32
    type AttrGetType PixbufNChannelsPropertyInfo = Int32
    type AttrLabel PixbufNChannelsPropertyInfo = "n-channels"
    type AttrOrigin PixbufNChannelsPropertyInfo = Pixbuf
    attrGet = getPixbufNChannels
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructPixbufNChannels
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.nChannels"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#g:attr:nChannels"
        })
#endif

-- VVV Prop "pixel-bytes"
   -- Type: TInterface (Name {namespace = "GLib", name = "Bytes"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@pixel-bytes@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' pixbuf #pixelBytes
-- @
getPixbufPixelBytes :: (MonadIO m, IsPixbuf o) => o -> m (Maybe GLib.Bytes.Bytes)
getPixbufPixelBytes :: forall (m :: * -> *) o.
(MonadIO m, IsPixbuf o) =>
o -> m (Maybe Bytes)
getPixbufPixelBytes o
obj = IO (Maybe Bytes) -> m (Maybe Bytes)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Bytes) -> m (Maybe Bytes))
-> IO (Maybe Bytes) -> m (Maybe Bytes)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Bytes -> Bytes) -> IO (Maybe Bytes)
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj String
"pixel-bytes" ManagedPtr Bytes -> Bytes
GLib.Bytes.Bytes

-- | Construct a `GValueConstruct` with valid value for the “@pixel-bytes@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPixbufPixelBytes :: (IsPixbuf o, MIO.MonadIO m) => GLib.Bytes.Bytes -> m (GValueConstruct o)
constructPixbufPixelBytes :: forall o (m :: * -> *).
(IsPixbuf o, MonadIO m) =>
Bytes -> m (GValueConstruct o)
constructPixbufPixelBytes Bytes
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Bytes -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed String
"pixel-bytes" (Bytes -> Maybe Bytes
forall a. a -> Maybe a
P.Just Bytes
val)

#if defined(ENABLE_OVERLOADING)
data PixbufPixelBytesPropertyInfo
instance AttrInfo PixbufPixelBytesPropertyInfo where
    type AttrAllowedOps PixbufPixelBytesPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint PixbufPixelBytesPropertyInfo = IsPixbuf
    type AttrSetTypeConstraint PixbufPixelBytesPropertyInfo = (~) GLib.Bytes.Bytes
    type AttrTransferTypeConstraint PixbufPixelBytesPropertyInfo = (~) GLib.Bytes.Bytes
    type AttrTransferType PixbufPixelBytesPropertyInfo = GLib.Bytes.Bytes
    type AttrGetType PixbufPixelBytesPropertyInfo = (Maybe GLib.Bytes.Bytes)
    type AttrLabel PixbufPixelBytesPropertyInfo = "pixel-bytes"
    type AttrOrigin PixbufPixelBytesPropertyInfo = Pixbuf
    attrGet = getPixbufPixelBytes
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructPixbufPixelBytes
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixelBytes"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#g:attr:pixelBytes"
        })
#endif

-- VVV Prop "pixels"
   -- Type: TBasicType TPtr
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@pixels@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' pixbuf #pixels
-- @
getPixbufPixels :: (MonadIO m, IsPixbuf o) => o -> m (Ptr ())
getPixbufPixels :: forall (m :: * -> *) o. (MonadIO m, IsPixbuf o) => o -> m (Ptr ())
getPixbufPixels o
obj = IO (Ptr ()) -> m (Ptr ())
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Ptr ())
forall a b. GObject a => a -> String -> IO (Ptr b)
B.Properties.getObjectPropertyPtr o
obj String
"pixels"

-- | Construct a `GValueConstruct` with valid value for the “@pixels@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPixbufPixels :: (IsPixbuf o, MIO.MonadIO m) => Ptr () -> m (GValueConstruct o)
constructPixbufPixels :: forall o (m :: * -> *).
(IsPixbuf o, MonadIO m) =>
Ptr () -> m (GValueConstruct o)
constructPixbufPixels Ptr ()
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Ptr () -> IO (GValueConstruct o)
forall b o. String -> Ptr b -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyPtr String
"pixels" Ptr ()
val

#if defined(ENABLE_OVERLOADING)
data PixbufPixelsPropertyInfo
instance AttrInfo PixbufPixelsPropertyInfo where
    type AttrAllowedOps PixbufPixelsPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PixbufPixelsPropertyInfo = IsPixbuf
    type AttrSetTypeConstraint PixbufPixelsPropertyInfo = (~) (Ptr ())
    type AttrTransferTypeConstraint PixbufPixelsPropertyInfo = (~) (Ptr ())
    type AttrTransferType PixbufPixelsPropertyInfo = Ptr ()
    type AttrGetType PixbufPixelsPropertyInfo = (Ptr ())
    type AttrLabel PixbufPixelsPropertyInfo = "pixels"
    type AttrOrigin PixbufPixelsPropertyInfo = Pixbuf
    attrGet = getPixbufPixels
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructPixbufPixels
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixels"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#g:attr:pixels"
        })
#endif

-- VVV Prop "rowstride"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@rowstride@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' pixbuf #rowstride
-- @
getPixbufRowstride :: (MonadIO m, IsPixbuf o) => o -> m Int32
getPixbufRowstride :: forall (m :: * -> *) o. (MonadIO m, IsPixbuf o) => o -> m Int32
getPixbufRowstride o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"rowstride"

-- | Construct a `GValueConstruct` with valid value for the “@rowstride@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPixbufRowstride :: (IsPixbuf o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructPixbufRowstride :: forall o (m :: * -> *).
(IsPixbuf o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructPixbufRowstride Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"rowstride" Int32
val

#if defined(ENABLE_OVERLOADING)
data PixbufRowstridePropertyInfo
instance AttrInfo PixbufRowstridePropertyInfo where
    type AttrAllowedOps PixbufRowstridePropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PixbufRowstridePropertyInfo = IsPixbuf
    type AttrSetTypeConstraint PixbufRowstridePropertyInfo = (~) Int32
    type AttrTransferTypeConstraint PixbufRowstridePropertyInfo = (~) Int32
    type AttrTransferType PixbufRowstridePropertyInfo = Int32
    type AttrGetType PixbufRowstridePropertyInfo = Int32
    type AttrLabel PixbufRowstridePropertyInfo = "rowstride"
    type AttrOrigin PixbufRowstridePropertyInfo = Pixbuf
    attrGet = getPixbufRowstride
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructPixbufRowstride
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.rowstride"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#g:attr:rowstride"
        })
#endif

-- VVV Prop "width"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@width@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' pixbuf #width
-- @
getPixbufWidth :: (MonadIO m, IsPixbuf o) => o -> m Int32
getPixbufWidth :: forall (m :: * -> *) o. (MonadIO m, IsPixbuf o) => o -> m Int32
getPixbufWidth o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"width"

-- | Construct a `GValueConstruct` with valid value for the “@width@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPixbufWidth :: (IsPixbuf o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructPixbufWidth :: forall o (m :: * -> *).
(IsPixbuf o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructPixbufWidth Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"width" Int32
val

#if defined(ENABLE_OVERLOADING)
data PixbufWidthPropertyInfo
instance AttrInfo PixbufWidthPropertyInfo where
    type AttrAllowedOps PixbufWidthPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PixbufWidthPropertyInfo = IsPixbuf
    type AttrSetTypeConstraint PixbufWidthPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint PixbufWidthPropertyInfo = (~) Int32
    type AttrTransferType PixbufWidthPropertyInfo = Int32
    type AttrGetType PixbufWidthPropertyInfo = Int32
    type AttrLabel PixbufWidthPropertyInfo = "width"
    type AttrOrigin PixbufWidthPropertyInfo = Pixbuf
    attrGet = getPixbufWidth
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructPixbufWidth
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.width"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#g:attr:width"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Pixbuf
type instance O.AttributeList Pixbuf = PixbufAttributeList
type PixbufAttributeList = ('[ '("bitsPerSample", PixbufBitsPerSamplePropertyInfo), '("colorspace", PixbufColorspacePropertyInfo), '("hasAlpha", PixbufHasAlphaPropertyInfo), '("height", PixbufHeightPropertyInfo), '("nChannels", PixbufNChannelsPropertyInfo), '("pixelBytes", PixbufPixelBytesPropertyInfo), '("pixels", PixbufPixelsPropertyInfo), '("rowstride", PixbufRowstridePropertyInfo), '("width", PixbufWidthPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
pixbufBitsPerSample :: AttrLabelProxy "bitsPerSample"
pixbufBitsPerSample = AttrLabelProxy

pixbufColorspace :: AttrLabelProxy "colorspace"
pixbufColorspace = AttrLabelProxy

pixbufHasAlpha :: AttrLabelProxy "hasAlpha"
pixbufHasAlpha = AttrLabelProxy

pixbufHeight :: AttrLabelProxy "height"
pixbufHeight = AttrLabelProxy

pixbufNChannels :: AttrLabelProxy "nChannels"
pixbufNChannels = AttrLabelProxy

pixbufPixelBytes :: AttrLabelProxy "pixelBytes"
pixbufPixelBytes = AttrLabelProxy

pixbufPixels :: AttrLabelProxy "pixels"
pixbufPixels = AttrLabelProxy

pixbufRowstride :: AttrLabelProxy "rowstride"
pixbufRowstride = AttrLabelProxy

pixbufWidth :: AttrLabelProxy "width"
pixbufWidth = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Pixbuf = PixbufSignalList
type PixbufSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method Pixbuf::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "colorspace"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Colorspace" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Color space for image"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "has_alpha"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Whether the image should have transparency information"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "bits_per_sample"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Number of bits per color sample"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Width of image in pixels, must be > 0"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Height of image in pixels, must be > 0"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_new" gdk_pixbuf_new :: 
    CUInt ->                                -- colorspace : TInterface (Name {namespace = "GdkPixbuf", name = "Colorspace"})
    CInt ->                                 -- has_alpha : TBasicType TBoolean
    Int32 ->                                -- bits_per_sample : TBasicType TInt
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    IO (Ptr Pixbuf)

-- | Creates a new @GdkPixbuf@ structure and allocates a buffer for it.
-- 
-- If the allocation of the buffer failed, this function will return @NULL@.
-- 
-- The buffer has an optimal rowstride. Note that the buffer is not cleared;
-- you will have to fill it completely yourself.
pixbufNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GdkPixbuf.Enums.Colorspace
    -- ^ /@colorspace@/: Color space for image
    -> Bool
    -- ^ /@hasAlpha@/: Whether the image should have transparency information
    -> Int32
    -- ^ /@bitsPerSample@/: Number of bits per color sample
    -> Int32
    -- ^ /@width@/: Width of image in pixels, must be > 0
    -> Int32
    -- ^ /@height@/: Height of image in pixels, must be > 0
    -> m (Maybe Pixbuf)
    -- ^ __Returns:__ A newly-created pixel buffer
pixbufNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Colorspace -> Bool -> Int32 -> Int32 -> Int32 -> m (Maybe Pixbuf)
pixbufNew Colorspace
colorspace Bool
hasAlpha Int32
bitsPerSample Int32
width Int32
height = IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Pixbuf) -> m (Maybe Pixbuf))
-> IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ do
    let colorspace' :: CUInt
colorspace' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Colorspace -> Int) -> Colorspace -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Colorspace -> Int
forall a. Enum a => a -> Int
fromEnum) Colorspace
colorspace
    let hasAlpha' :: CInt
hasAlpha' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
hasAlpha
    Ptr Pixbuf
result <- CUInt -> CInt -> Int32 -> Int32 -> Int32 -> IO (Ptr Pixbuf)
gdk_pixbuf_new CUInt
colorspace' CInt
hasAlpha' Int32
bitsPerSample Int32
width Int32
height
    Maybe Pixbuf
maybeResult <- Ptr Pixbuf -> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Pixbuf
result ((Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf))
-> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ \Ptr Pixbuf
result' -> do
        Pixbuf
result'' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
Pixbuf) Ptr Pixbuf
result'
        Pixbuf -> IO Pixbuf
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result''
    Maybe Pixbuf -> IO (Maybe Pixbuf)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
maybeResult

#if defined(ENABLE_OVERLOADING)
#endif

-- method Pixbuf::new_from_bytes
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "data"
--           , argType = TInterface Name { namespace = "GLib" , name = "Bytes" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Image data in 8-bit/sample packed format inside a #GBytes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "colorspace"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Colorspace" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Colorspace for the image data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "has_alpha"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Whether the data has an opacity channel"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "bits_per_sample"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Number of bits per sample"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Width of the image in pixels, must be > 0"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Height of the image in pixels, must be > 0"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "rowstride"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Distance in bytes between row starts"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_new_from_bytes" gdk_pixbuf_new_from_bytes :: 
    Ptr GLib.Bytes.Bytes ->                 -- data : TInterface (Name {namespace = "GLib", name = "Bytes"})
    CUInt ->                                -- colorspace : TInterface (Name {namespace = "GdkPixbuf", name = "Colorspace"})
    CInt ->                                 -- has_alpha : TBasicType TBoolean
    Int32 ->                                -- bits_per_sample : TBasicType TInt
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    Int32 ->                                -- rowstride : TBasicType TInt
    IO (Ptr Pixbuf)

-- | Creates a new t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf' out of in-memory readonly image data.
-- 
-- Currently only RGB images with 8 bits per sample are supported.
-- 
-- This is the @GBytes@ variant of 'GI.GdkPixbuf.Objects.Pixbuf.pixbufNewFromData', useful
-- for language bindings.
-- 
-- /Since: 2.32/
pixbufNewFromBytes ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GLib.Bytes.Bytes
    -- ^ /@data@/: Image data in 8-bit\/sample packed format inside a t'GI.GLib.Structs.Bytes.Bytes'
    -> GdkPixbuf.Enums.Colorspace
    -- ^ /@colorspace@/: Colorspace for the image data
    -> Bool
    -- ^ /@hasAlpha@/: Whether the data has an opacity channel
    -> Int32
    -- ^ /@bitsPerSample@/: Number of bits per sample
    -> Int32
    -- ^ /@width@/: Width of the image in pixels, must be > 0
    -> Int32
    -- ^ /@height@/: Height of the image in pixels, must be > 0
    -> Int32
    -- ^ /@rowstride@/: Distance in bytes between row starts
    -> m Pixbuf
    -- ^ __Returns:__ A newly-created pixbuf
pixbufNewFromBytes :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bytes
-> Colorspace
-> Bool
-> Int32
-> Int32
-> Int32
-> Int32
-> m Pixbuf
pixbufNewFromBytes Bytes
data_ Colorspace
colorspace Bool
hasAlpha Int32
bitsPerSample Int32
width Int32
height Int32
rowstride = IO Pixbuf -> m Pixbuf
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Pixbuf -> m Pixbuf) -> IO Pixbuf -> m Pixbuf
forall a b. (a -> b) -> a -> b
$ do
    Ptr Bytes
data_' <- Bytes -> IO (Ptr Bytes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bytes
data_
    let colorspace' :: CUInt
colorspace' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Colorspace -> Int) -> Colorspace -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Colorspace -> Int
forall a. Enum a => a -> Int
fromEnum) Colorspace
colorspace
    let hasAlpha' :: CInt
hasAlpha' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
hasAlpha
    Ptr Pixbuf
result <- Ptr Bytes
-> CUInt
-> CInt
-> Int32
-> Int32
-> Int32
-> Int32
-> IO (Ptr Pixbuf)
gdk_pixbuf_new_from_bytes Ptr Bytes
data_' CUInt
colorspace' CInt
hasAlpha' Int32
bitsPerSample Int32
width Int32
height Int32
rowstride
    Text -> Ptr Pixbuf -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pixbufNewFromBytes" Ptr Pixbuf
result
    Pixbuf
result' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
Pixbuf) Ptr Pixbuf
result
    Bytes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bytes
data_
    Pixbuf -> IO Pixbuf
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Pixbuf::new_from_data
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "data"
--           , argType = TCArray False (-1) (-1) (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Image data in 8-bit/sample packed format"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "colorspace"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Colorspace" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Colorspace for the image data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "has_alpha"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Whether the data has an opacity channel"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "bits_per_sample"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Number of bits per sample"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Width of the image in pixels, must be > 0"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Height of the image in pixels, must be > 0"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "rowstride"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Distance in bytes between row starts"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "destroy_fn"
--           , argType =
--               TInterface
--                 Name { namespace = "GdkPixbuf" , name = "PixbufDestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Function used to free the data when the pixbuf's reference count\ndrops to zero, or %NULL if the data should not be freed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 8
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "destroy_fn_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Closure data to pass to the destroy notification function"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_new_from_data" gdk_pixbuf_new_from_data :: 
    Ptr Word8 ->                            -- data : TCArray False (-1) (-1) (TBasicType TUInt8)
    CUInt ->                                -- colorspace : TInterface (Name {namespace = "GdkPixbuf", name = "Colorspace"})
    CInt ->                                 -- has_alpha : TBasicType TBoolean
    Int32 ->                                -- bits_per_sample : TBasicType TInt
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    Int32 ->                                -- rowstride : TBasicType TInt
    FunPtr GdkPixbuf.Callbacks.C_PixbufDestroyNotify -> -- destroy_fn : TInterface (Name {namespace = "GdkPixbuf", name = "PixbufDestroyNotify"})
    Ptr () ->                               -- destroy_fn_data : TBasicType TPtr
    IO (Ptr Pixbuf)

-- | Creates a new t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf' out of in-memory image data.
-- 
-- Currently only RGB images with 8 bits per sample are supported.
-- 
-- Since you are providing a pre-allocated pixel buffer, you must also
-- specify a way to free that data.  This is done with a function of
-- type @GdkPixbufDestroyNotify@.  When a pixbuf created with is
-- finalized, your destroy notification function will be called, and
-- it is its responsibility to free the pixel array.
-- 
-- See also: 'GI.GdkPixbuf.Objects.Pixbuf.pixbufNewFromBytes'
pixbufNewFromData ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Ptr Word8
    -- ^ /@data@/: Image data in 8-bit\/sample packed format
    -> GdkPixbuf.Enums.Colorspace
    -- ^ /@colorspace@/: Colorspace for the image data
    -> Bool
    -- ^ /@hasAlpha@/: Whether the data has an opacity channel
    -> Int32
    -- ^ /@bitsPerSample@/: Number of bits per sample
    -> Int32
    -- ^ /@width@/: Width of the image in pixels, must be > 0
    -> Int32
    -- ^ /@height@/: Height of the image in pixels, must be > 0
    -> Int32
    -- ^ /@rowstride@/: Distance in bytes between row starts
    -> Maybe (GdkPixbuf.Callbacks.PixbufDestroyNotify)
    -- ^ /@destroyFn@/: Function used to free the data when the pixbuf\'s reference count
    -- drops to zero, or 'P.Nothing' if the data should not be freed
    -> m Pixbuf
    -- ^ __Returns:__ A newly-created pixbuf
pixbufNewFromData :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Ptr Word8
-> Colorspace
-> Bool
-> Int32
-> Int32
-> Int32
-> Int32
-> Maybe PixbufDestroyNotify
-> m Pixbuf
pixbufNewFromData Ptr Word8
data_ Colorspace
colorspace Bool
hasAlpha Int32
bitsPerSample Int32
width Int32
height Int32
rowstride Maybe PixbufDestroyNotify
destroyFn = IO Pixbuf -> m Pixbuf
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Pixbuf -> m Pixbuf) -> IO Pixbuf -> m Pixbuf
forall a b. (a -> b) -> a -> b
$ do
    let colorspace' :: CUInt
colorspace' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Colorspace -> Int) -> Colorspace -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Colorspace -> Int
forall a. Enum a => a -> Int
fromEnum) Colorspace
colorspace
    let hasAlpha' :: CInt
hasAlpha' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
hasAlpha
    FunPtr C_PixbufDestroyNotify
maybeDestroyFn <- case Maybe PixbufDestroyNotify
destroyFn of
        Maybe PixbufDestroyNotify
Nothing -> FunPtr C_PixbufDestroyNotify -> IO (FunPtr C_PixbufDestroyNotify)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_PixbufDestroyNotify
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just PixbufDestroyNotify
jDestroyFn -> do
            Ptr (FunPtr C_PixbufDestroyNotify)
ptrdestroyFn <- IO (Ptr (FunPtr C_PixbufDestroyNotify))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr GdkPixbuf.Callbacks.C_PixbufDestroyNotify))
            FunPtr C_PixbufDestroyNotify
jDestroyFn' <- C_PixbufDestroyNotify -> IO (FunPtr C_PixbufDestroyNotify)
GdkPixbuf.Callbacks.mk_PixbufDestroyNotify (Maybe (Ptr (FunPtr C_PixbufDestroyNotify))
-> C_PixbufDestroyNotify -> C_PixbufDestroyNotify
GdkPixbuf.Callbacks.wrap_PixbufDestroyNotify (Ptr (FunPtr C_PixbufDestroyNotify)
-> Maybe (Ptr (FunPtr C_PixbufDestroyNotify))
forall a. a -> Maybe a
Just Ptr (FunPtr C_PixbufDestroyNotify)
ptrdestroyFn) (PixbufDestroyNotify -> C_PixbufDestroyNotify
GdkPixbuf.Callbacks.drop_closures_PixbufDestroyNotify PixbufDestroyNotify
jDestroyFn))
            Ptr (FunPtr C_PixbufDestroyNotify)
-> FunPtr C_PixbufDestroyNotify -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_PixbufDestroyNotify)
ptrdestroyFn FunPtr C_PixbufDestroyNotify
jDestroyFn'
            FunPtr C_PixbufDestroyNotify -> IO (FunPtr C_PixbufDestroyNotify)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_PixbufDestroyNotify
jDestroyFn'
    let destroyFnData :: Ptr a
destroyFnData = Ptr a
forall a. Ptr a
nullPtr
    Ptr Pixbuf
result <- Ptr Word8
-> CUInt
-> CInt
-> Int32
-> Int32
-> Int32
-> Int32
-> FunPtr C_PixbufDestroyNotify
-> Ptr ()
-> IO (Ptr Pixbuf)
gdk_pixbuf_new_from_data Ptr Word8
data_ CUInt
colorspace' CInt
hasAlpha' Int32
bitsPerSample Int32
width Int32
height Int32
rowstride FunPtr C_PixbufDestroyNotify
maybeDestroyFn Ptr ()
forall a. Ptr a
destroyFnData
    Text -> Ptr Pixbuf -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pixbufNewFromData" Ptr Pixbuf
result
    Pixbuf
result' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
Pixbuf) Ptr Pixbuf
result
    Pixbuf -> IO Pixbuf
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Pixbuf::new_from_file
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "filename"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Name of file to load, in the GLib file\n  name encoding"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : True
-- Skip return : False

foreign import ccall "gdk_pixbuf_new_from_file" gdk_pixbuf_new_from_file :: 
    CString ->                              -- filename : TBasicType TFileName
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Pixbuf)

-- | Creates a new pixbuf by loading an image from a file.
-- 
-- The file format is detected automatically.
-- 
-- If @NULL@ is returned, then /@error@/ will be set. Possible errors are:
-- 
--  - the file could not be opened
--  - there is no loader for the file\'s format
--  - there is not enough memory to allocate the image buffer
--  - the image buffer contains invalid data
-- 
-- The error domains are @GDK_PIXBUF_ERROR@ and @G_FILE_ERROR@.
pixbufNewFromFile ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [Char]
    -- ^ /@filename@/: Name of file to load, in the GLib file
    --   name encoding
    -> m (Maybe Pixbuf)
    -- ^ __Returns:__ A newly-created pixbuf /(Can throw 'Data.GI.Base.GError.GError')/
pixbufNewFromFile :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> m (Maybe Pixbuf)
pixbufNewFromFile String
filename = IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Pixbuf) -> m (Maybe Pixbuf))
-> IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ do
    CString
filename' <- String -> IO CString
stringToCString String
filename
    IO (Maybe Pixbuf) -> IO () -> IO (Maybe Pixbuf)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Pixbuf
result <- (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf))
-> (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a b. (a -> b) -> a -> b
$ CString -> Ptr (Ptr GError) -> IO (Ptr Pixbuf)
gdk_pixbuf_new_from_file CString
filename'
        Maybe Pixbuf
maybeResult <- Ptr Pixbuf -> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Pixbuf
result ((Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf))
-> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ \Ptr Pixbuf
result' -> do
            Pixbuf
result'' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
Pixbuf) Ptr Pixbuf
result'
            Pixbuf -> IO Pixbuf
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result''
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
        Maybe Pixbuf -> IO (Maybe Pixbuf)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
maybeResult
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method Pixbuf::new_from_file_at_scale
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "filename"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Name of file to load, in the GLib file\n    name encoding"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The width the image should have or -1 to not constrain the width"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The height the image should have or -1 to not constrain the height"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "preserve_aspect_ratio"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "`TRUE` to preserve the image's aspect ratio"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : True
-- Skip return : False

foreign import ccall "gdk_pixbuf_new_from_file_at_scale" gdk_pixbuf_new_from_file_at_scale :: 
    CString ->                              -- filename : TBasicType TFileName
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    CInt ->                                 -- preserve_aspect_ratio : TBasicType TBoolean
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Pixbuf)

-- | Creates a new pixbuf by loading an image from a file.
-- 
-- The file format is detected automatically.
-- 
-- If @NULL@ is returned, then /@error@/ will be set. Possible errors are:
-- 
--  - the file could not be opened
--  - there is no loader for the file\'s format
--  - there is not enough memory to allocate the image buffer
--  - the image buffer contains invalid data
-- 
-- The error domains are @GDK_PIXBUF_ERROR@ and @G_FILE_ERROR@.
-- 
-- The image will be scaled to fit in the requested size, optionally preserving
-- the image\'s aspect ratio.
-- 
-- When preserving the aspect ratio, a @width@ of -1 will cause the image
-- to be scaled to the exact given height, and a @height@ of -1 will cause
-- the image to be scaled to the exact given width. When not preserving
-- aspect ratio, a @width@ or @height@ of -1 means to not scale the image
-- at all in that dimension. Negative values for @width@ and @height@ are
-- allowed since 2.8.
-- 
-- /Since: 2.6/
pixbufNewFromFileAtScale ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [Char]
    -- ^ /@filename@/: Name of file to load, in the GLib file
    --     name encoding
    -> Int32
    -- ^ /@width@/: The width the image should have or -1 to not constrain the width
    -> Int32
    -- ^ /@height@/: The height the image should have or -1 to not constrain the height
    -> Bool
    -- ^ /@preserveAspectRatio@/: @TRUE@ to preserve the image\'s aspect ratio
    -> m (Maybe Pixbuf)
    -- ^ __Returns:__ A newly-created pixbuf /(Can throw 'Data.GI.Base.GError.GError')/
pixbufNewFromFileAtScale :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> Int32 -> Int32 -> Bool -> m (Maybe Pixbuf)
pixbufNewFromFileAtScale String
filename Int32
width Int32
height Bool
preserveAspectRatio = IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Pixbuf) -> m (Maybe Pixbuf))
-> IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ do
    CString
filename' <- String -> IO CString
stringToCString String
filename
    let preserveAspectRatio' :: CInt
preserveAspectRatio' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
preserveAspectRatio
    IO (Maybe Pixbuf) -> IO () -> IO (Maybe Pixbuf)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Pixbuf
result <- (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf))
-> (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a b. (a -> b) -> a -> b
$ CString
-> Int32 -> Int32 -> CInt -> Ptr (Ptr GError) -> IO (Ptr Pixbuf)
gdk_pixbuf_new_from_file_at_scale CString
filename' Int32
width Int32
height CInt
preserveAspectRatio'
        Maybe Pixbuf
maybeResult <- Ptr Pixbuf -> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Pixbuf
result ((Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf))
-> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ \Ptr Pixbuf
result' -> do
            Pixbuf
result'' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
Pixbuf) Ptr Pixbuf
result'
            Pixbuf -> IO Pixbuf
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result''
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
        Maybe Pixbuf -> IO (Maybe Pixbuf)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
maybeResult
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method Pixbuf::new_from_file_at_size
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "filename"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Name of file to load, in the GLib file\n    name encoding"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The width the image should have or -1 to not constrain the width"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The height the image should have or -1 to not constrain the height"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : True
-- Skip return : False

foreign import ccall "gdk_pixbuf_new_from_file_at_size" gdk_pixbuf_new_from_file_at_size :: 
    CString ->                              -- filename : TBasicType TFileName
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Pixbuf)

-- | Creates a new pixbuf by loading an image from a file.
-- 
-- The file format is detected automatically.
-- 
-- If @NULL@ is returned, then /@error@/ will be set. Possible errors are:
-- 
--  - the file could not be opened
--  - there is no loader for the file\'s format
--  - there is not enough memory to allocate the image buffer
--  - the image buffer contains invalid data
-- 
-- The error domains are @GDK_PIXBUF_ERROR@ and @G_FILE_ERROR@.
-- 
-- The image will be scaled to fit in the requested size, preserving
-- the image\'s aspect ratio. Note that the returned pixbuf may be smaller
-- than @width@ x @height@, if the aspect ratio requires it. To load
-- and image at the requested size, regardless of aspect ratio, use
-- 'GI.GdkPixbuf.Objects.Pixbuf.pixbufNewFromFileAtScale'.
-- 
-- /Since: 2.4/
pixbufNewFromFileAtSize ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [Char]
    -- ^ /@filename@/: Name of file to load, in the GLib file
    --     name encoding
    -> Int32
    -- ^ /@width@/: The width the image should have or -1 to not constrain the width
    -> Int32
    -- ^ /@height@/: The height the image should have or -1 to not constrain the height
    -> m (Maybe Pixbuf)
    -- ^ __Returns:__ A newly-created pixbuf /(Can throw 'Data.GI.Base.GError.GError')/
pixbufNewFromFileAtSize :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> Int32 -> Int32 -> m (Maybe Pixbuf)
pixbufNewFromFileAtSize String
filename Int32
width Int32
height = IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Pixbuf) -> m (Maybe Pixbuf))
-> IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ do
    CString
filename' <- String -> IO CString
stringToCString String
filename
    IO (Maybe Pixbuf) -> IO () -> IO (Maybe Pixbuf)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Pixbuf
result <- (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf))
-> (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a b. (a -> b) -> a -> b
$ CString -> Int32 -> Int32 -> Ptr (Ptr GError) -> IO (Ptr Pixbuf)
gdk_pixbuf_new_from_file_at_size CString
filename' Int32
width Int32
height
        Maybe Pixbuf
maybeResult <- Ptr Pixbuf -> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Pixbuf
result ((Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf))
-> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ \Ptr Pixbuf
result' -> do
            Pixbuf
result'' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
Pixbuf) Ptr Pixbuf
result'
            Pixbuf -> IO Pixbuf
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result''
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
        Maybe Pixbuf -> IO (Maybe Pixbuf)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
maybeResult
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method Pixbuf::new_from_inline
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "data_length"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Length in bytes of the `data` argument or -1 to\n  disable length checks"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "data"
--           , argType = TCArray False (-1) 0 (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Byte data containing a\n  serialized `GdkPixdata` structure"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "copy_pixels"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Whether to copy the pixel data, or use direct pointers\n  `data` for the resulting pixbuf"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "data_length"
--              , argType = TBasicType TInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just
--                          "Length in bytes of the `data` argument or -1 to\n  disable length checks"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : True
-- Skip return : False

foreign import ccall "gdk_pixbuf_new_from_inline" gdk_pixbuf_new_from_inline :: 
    Int32 ->                                -- data_length : TBasicType TInt
    Ptr Word8 ->                            -- data : TCArray False (-1) 0 (TBasicType TUInt8)
    CInt ->                                 -- copy_pixels : TBasicType TBoolean
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Pixbuf)

{-# DEPRECATED pixbufNewFromInline ["(Since version 2.32)","Use @GResource@ instead."] #-}
-- | Creates a @GdkPixbuf@ from a flat representation that is suitable for
-- storing as inline data in a program.
-- 
-- This is useful if you want to ship a program with images, but don\'t want
-- to depend on any external files.
-- 
-- GdkPixbuf ships with a program called @gdk-pixbuf-csource@, which allows
-- for conversion of @GdkPixbuf@s into such a inline representation.
-- 
-- In almost all cases, you should pass the @--raw@ option to
-- @gdk-pixbuf-csource@. A sample invocation would be:
-- 
-- >gdk-pixbuf-csource --raw --name=myimage_inline myimage.png
-- 
-- 
-- For the typical case where the inline pixbuf is read-only static data,
-- you don\'t need to copy the pixel data unless you intend to write to
-- it, so you can pass @FALSE@ for @copy_pixels@. If you pass @--rle@ to
-- @gdk-pixbuf-csource@, a copy will be made even if @copy_pixels@ is @FALSE@,
-- so using this option is generally a bad idea.
-- 
-- If you create a pixbuf from const inline data compiled into your
-- program, it\'s probably safe to ignore errors and disable length checks,
-- since things will always succeed:
-- 
-- 
-- === /c code/
-- >pixbuf = gdk_pixbuf_new_from_inline (-1, myimage_inline, FALSE, NULL);
-- 
-- 
-- For non-const inline data, you could get out of memory. For untrusted
-- inline data located at runtime, you could have corrupt inline data in
-- addition.
pixbufNewFromInline ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteString
    -- ^ /@data@/: Byte data containing a
    --   serialized @GdkPixdata@ structure
    -> Bool
    -- ^ /@copyPixels@/: Whether to copy the pixel data, or use direct pointers
    --   @data@ for the resulting pixbuf
    -> m Pixbuf
    -- ^ __Returns:__ A newly-created pixbuf /(Can throw 'Data.GI.Base.GError.GError')/
pixbufNewFromInline :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ByteString -> Bool -> m Pixbuf
pixbufNewFromInline ByteString
data_ Bool
copyPixels = IO Pixbuf -> m Pixbuf
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Pixbuf -> m Pixbuf) -> IO Pixbuf -> m Pixbuf
forall a b. (a -> b) -> a -> b
$ do
    let dataLength :: Int32
dataLength = Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
data_
    Ptr Word8
data_' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
data_
    let copyPixels' :: CInt
copyPixels' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
copyPixels
    IO Pixbuf -> IO () -> IO Pixbuf
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Pixbuf
result <- (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf))
-> (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a b. (a -> b) -> a -> b
$ Int32 -> Ptr Word8 -> CInt -> Ptr (Ptr GError) -> IO (Ptr Pixbuf)
gdk_pixbuf_new_from_inline Int32
dataLength Ptr Word8
data_' CInt
copyPixels'
        Text -> Ptr Pixbuf -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pixbufNewFromInline" Ptr Pixbuf
result
        Pixbuf
result' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
Pixbuf) Ptr Pixbuf
result
        PixbufDestroyNotify
forall a. Ptr a -> IO ()
freeMem Ptr Word8
data_'
        Pixbuf -> IO Pixbuf
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result'
     ) (do
        PixbufDestroyNotify
forall a. Ptr a -> IO ()
freeMem Ptr Word8
data_'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method Pixbuf::new_from_resource
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "resource_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the path of the resource file"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : True
-- Skip return : False

foreign import ccall "gdk_pixbuf_new_from_resource" gdk_pixbuf_new_from_resource :: 
    CString ->                              -- resource_path : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Pixbuf)

-- | Creates a new pixbuf by loading an image from an resource.
-- 
-- The file format is detected automatically. If @NULL@ is returned, then
-- /@error@/ will be set.
-- 
-- /Since: 2.26/
pixbufNewFromResource ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@resourcePath@/: the path of the resource file
    -> m (Maybe Pixbuf)
    -- ^ __Returns:__ A newly-created pixbuf /(Can throw 'Data.GI.Base.GError.GError')/
pixbufNewFromResource :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m (Maybe Pixbuf)
pixbufNewFromResource Text
resourcePath = IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Pixbuf) -> m (Maybe Pixbuf))
-> IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ do
    CString
resourcePath' <- Text -> IO CString
textToCString Text
resourcePath
    IO (Maybe Pixbuf) -> IO () -> IO (Maybe Pixbuf)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Pixbuf
result <- (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf))
-> (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a b. (a -> b) -> a -> b
$ CString -> Ptr (Ptr GError) -> IO (Ptr Pixbuf)
gdk_pixbuf_new_from_resource CString
resourcePath'
        Maybe Pixbuf
maybeResult <- Ptr Pixbuf -> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Pixbuf
result ((Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf))
-> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ \Ptr Pixbuf
result' -> do
            Pixbuf
result'' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
Pixbuf) Ptr Pixbuf
result'
            Pixbuf -> IO Pixbuf
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result''
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
resourcePath'
        Maybe Pixbuf -> IO (Maybe Pixbuf)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
maybeResult
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
resourcePath'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method Pixbuf::new_from_resource_at_scale
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "resource_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the path of the resource file"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The width the image should have or -1 to not constrain the width"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The height the image should have or -1 to not constrain the height"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "preserve_aspect_ratio"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "`TRUE` to preserve the image's aspect ratio"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : True
-- Skip return : False

foreign import ccall "gdk_pixbuf_new_from_resource_at_scale" gdk_pixbuf_new_from_resource_at_scale :: 
    CString ->                              -- resource_path : TBasicType TUTF8
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    CInt ->                                 -- preserve_aspect_ratio : TBasicType TBoolean
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Pixbuf)

-- | Creates a new pixbuf by loading an image from an resource.
-- 
-- The file format is detected automatically. If @NULL@ is returned, then
-- /@error@/ will be set.
-- 
-- The image will be scaled to fit in the requested size, optionally
-- preserving the image\'s aspect ratio. When preserving the aspect ratio,
-- a /@width@/ of -1 will cause the image to be scaled to the exact given
-- height, and a /@height@/ of -1 will cause the image to be scaled to the
-- exact given width. When not preserving aspect ratio, a /@width@/ or
-- /@height@/ of -1 means to not scale the image at all in that dimension.
-- 
-- The stream is not closed.
-- 
-- /Since: 2.26/
pixbufNewFromResourceAtScale ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@resourcePath@/: the path of the resource file
    -> Int32
    -- ^ /@width@/: The width the image should have or -1 to not constrain the width
    -> Int32
    -- ^ /@height@/: The height the image should have or -1 to not constrain the height
    -> Bool
    -- ^ /@preserveAspectRatio@/: @TRUE@ to preserve the image\'s aspect ratio
    -> m (Maybe Pixbuf)
    -- ^ __Returns:__ A newly-created pixbuf /(Can throw 'Data.GI.Base.GError.GError')/
pixbufNewFromResourceAtScale :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> Int32 -> Int32 -> Bool -> m (Maybe Pixbuf)
pixbufNewFromResourceAtScale Text
resourcePath Int32
width Int32
height Bool
preserveAspectRatio = IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Pixbuf) -> m (Maybe Pixbuf))
-> IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ do
    CString
resourcePath' <- Text -> IO CString
textToCString Text
resourcePath
    let preserveAspectRatio' :: CInt
preserveAspectRatio' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
preserveAspectRatio
    IO (Maybe Pixbuf) -> IO () -> IO (Maybe Pixbuf)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Pixbuf
result <- (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf))
-> (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a b. (a -> b) -> a -> b
$ CString
-> Int32 -> Int32 -> CInt -> Ptr (Ptr GError) -> IO (Ptr Pixbuf)
gdk_pixbuf_new_from_resource_at_scale CString
resourcePath' Int32
width Int32
height CInt
preserveAspectRatio'
        Maybe Pixbuf
maybeResult <- Ptr Pixbuf -> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Pixbuf
result ((Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf))
-> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ \Ptr Pixbuf
result' -> do
            Pixbuf
result'' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
Pixbuf) Ptr Pixbuf
result'
            Pixbuf -> IO Pixbuf
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result''
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
resourcePath'
        Maybe Pixbuf -> IO (Maybe Pixbuf)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
maybeResult
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
resourcePath'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method Pixbuf::new_from_stream
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "stream"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "InputStream" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GInputStream` to load the pixbuf from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "optional `GCancellable` object, `NULL` to ignore"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : True
-- Skip return : False

foreign import ccall "gdk_pixbuf_new_from_stream" gdk_pixbuf_new_from_stream :: 
    Ptr Gio.InputStream.InputStream ->      -- stream : TInterface (Name {namespace = "Gio", name = "InputStream"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Pixbuf)

-- | Creates a new pixbuf by loading an image from an input stream.
-- 
-- The file format is detected automatically.
-- 
-- If @NULL@ is returned, then @error@ will be set.
-- 
-- The @cancellable@ can be used to abort the operation from another thread.
-- If the operation was cancelled, the error @G_IO_ERROR_CANCELLED@ will be
-- returned. Other possible errors are in the @GDK_PIXBUF_ERROR@ and
-- @G_IO_ERROR@ domains.
-- 
-- The stream is not closed.
-- 
-- /Since: 2.14/
pixbufNewFromStream ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.InputStream.IsInputStream a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@stream@/: a @GInputStream@ to load the pixbuf from
    -> Maybe (b)
    -- ^ /@cancellable@/: optional @GCancellable@ object, @NULL@ to ignore
    -> m (Maybe Pixbuf)
    -- ^ __Returns:__ A newly-created pixbuf /(Can throw 'Data.GI.Base.GError.GError')/
pixbufNewFromStream :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsInputStream a, IsCancellable b) =>
a -> Maybe b -> m (Maybe Pixbuf)
pixbufNewFromStream a
stream Maybe b
cancellable = IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Pixbuf) -> m (Maybe Pixbuf))
-> IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ do
    Ptr InputStream
stream' <- a -> IO (Ptr InputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO (Maybe Pixbuf) -> IO () -> IO (Maybe Pixbuf)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Pixbuf
result <- (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf))
-> (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a b. (a -> b) -> a -> b
$ Ptr InputStream
-> Ptr Cancellable -> Ptr (Ptr GError) -> IO (Ptr Pixbuf)
gdk_pixbuf_new_from_stream Ptr InputStream
stream' Ptr Cancellable
maybeCancellable
        Maybe Pixbuf
maybeResult <- Ptr Pixbuf -> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Pixbuf
result ((Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf))
-> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ \Ptr Pixbuf
result' -> do
            Pixbuf
result'' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
Pixbuf) Ptr Pixbuf
result'
            Pixbuf -> IO Pixbuf
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result''
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe Pixbuf -> IO (Maybe Pixbuf)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
maybeResult
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method Pixbuf::new_from_stream_at_scale
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "stream"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "InputStream" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GInputStream` to load the pixbuf from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The width the image should have or -1 to not constrain the width"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The height the image should have or -1 to not constrain the height"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "preserve_aspect_ratio"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "`TRUE` to preserve the image's aspect ratio"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "optional `GCancellable` object, `NULL` to ignore"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : True
-- Skip return : False

foreign import ccall "gdk_pixbuf_new_from_stream_at_scale" gdk_pixbuf_new_from_stream_at_scale :: 
    Ptr Gio.InputStream.InputStream ->      -- stream : TInterface (Name {namespace = "Gio", name = "InputStream"})
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    CInt ->                                 -- preserve_aspect_ratio : TBasicType TBoolean
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Pixbuf)

-- | Creates a new pixbuf by loading an image from an input stream.
-- 
-- The file format is detected automatically. If @NULL@ is returned, then
-- /@error@/ will be set. The /@cancellable@/ can be used to abort the operation
-- from another thread. If the operation was cancelled, the error
-- @G_IO_ERROR_CANCELLED@ will be returned. Other possible errors are in
-- the @GDK_PIXBUF_ERROR@ and @G_IO_ERROR@ domains.
-- 
-- The image will be scaled to fit in the requested size, optionally
-- preserving the image\'s aspect ratio.
-- 
-- When preserving the aspect ratio, a @width@ of -1 will cause the image to be
-- scaled to the exact given height, and a @height@ of -1 will cause the image
-- to be scaled to the exact given width. If both @width@ and @height@ are
-- given, this function will behave as if the smaller of the two values
-- is passed as -1.
-- 
-- When not preserving aspect ratio, a @width@ or @height@ of -1 means to not
-- scale the image at all in that dimension.
-- 
-- The stream is not closed.
-- 
-- /Since: 2.14/
pixbufNewFromStreamAtScale ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.InputStream.IsInputStream a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@stream@/: a @GInputStream@ to load the pixbuf from
    -> Int32
    -- ^ /@width@/: The width the image should have or -1 to not constrain the width
    -> Int32
    -- ^ /@height@/: The height the image should have or -1 to not constrain the height
    -> Bool
    -- ^ /@preserveAspectRatio@/: @TRUE@ to preserve the image\'s aspect ratio
    -> Maybe (b)
    -- ^ /@cancellable@/: optional @GCancellable@ object, @NULL@ to ignore
    -> m (Maybe Pixbuf)
    -- ^ __Returns:__ A newly-created pixbuf /(Can throw 'Data.GI.Base.GError.GError')/
pixbufNewFromStreamAtScale :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsInputStream a, IsCancellable b) =>
a -> Int32 -> Int32 -> Bool -> Maybe b -> m (Maybe Pixbuf)
pixbufNewFromStreamAtScale a
stream Int32
width Int32
height Bool
preserveAspectRatio Maybe b
cancellable = IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Pixbuf) -> m (Maybe Pixbuf))
-> IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ do
    Ptr InputStream
stream' <- a -> IO (Ptr InputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
    let preserveAspectRatio' :: CInt
preserveAspectRatio' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
preserveAspectRatio
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO (Maybe Pixbuf) -> IO () -> IO (Maybe Pixbuf)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Pixbuf
result <- (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf))
-> (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a b. (a -> b) -> a -> b
$ Ptr InputStream
-> Int32
-> Int32
-> CInt
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO (Ptr Pixbuf)
gdk_pixbuf_new_from_stream_at_scale Ptr InputStream
stream' Int32
width Int32
height CInt
preserveAspectRatio' Ptr Cancellable
maybeCancellable
        Maybe Pixbuf
maybeResult <- Ptr Pixbuf -> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Pixbuf
result ((Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf))
-> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ \Ptr Pixbuf
result' -> do
            Pixbuf
result'' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
Pixbuf) Ptr Pixbuf
result'
            Pixbuf -> IO Pixbuf
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result''
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe Pixbuf -> IO (Maybe Pixbuf)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
maybeResult
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method Pixbuf::new_from_stream_finish
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "async_result"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GAsyncResult`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : True
-- Skip return : False

foreign import ccall "gdk_pixbuf_new_from_stream_finish" gdk_pixbuf_new_from_stream_finish :: 
    Ptr Gio.AsyncResult.AsyncResult ->      -- async_result : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Pixbuf)

-- | Finishes an asynchronous pixbuf creation operation started with
-- 'GI.GdkPixbuf.Objects.Pixbuf.pixbufNewFromStreamAsync'.
-- 
-- /Since: 2.24/
pixbufNewFromStreamFinish ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.AsyncResult.IsAsyncResult a) =>
    a
    -- ^ /@asyncResult@/: a @GAsyncResult@
    -> m (Maybe Pixbuf)
    -- ^ __Returns:__ the newly created pixbuf /(Can throw 'Data.GI.Base.GError.GError')/
pixbufNewFromStreamFinish :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAsyncResult a) =>
a -> m (Maybe Pixbuf)
pixbufNewFromStreamFinish a
asyncResult = IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Pixbuf) -> m (Maybe Pixbuf))
-> IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ do
    Ptr AsyncResult
asyncResult' <- a -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
asyncResult
    IO (Maybe Pixbuf) -> IO () -> IO (Maybe Pixbuf)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Pixbuf
result <- (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf))
-> (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a b. (a -> b) -> a -> b
$ Ptr AsyncResult -> Ptr (Ptr GError) -> IO (Ptr Pixbuf)
gdk_pixbuf_new_from_stream_finish Ptr AsyncResult
asyncResult'
        Maybe Pixbuf
maybeResult <- Ptr Pixbuf -> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Pixbuf
result ((Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf))
-> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ \Ptr Pixbuf
result' -> do
            Pixbuf
result'' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
Pixbuf) Ptr Pixbuf
result'
            Pixbuf -> IO Pixbuf
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result''
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
asyncResult
        Maybe Pixbuf -> IO (Maybe Pixbuf)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
maybeResult
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method Pixbuf::new_from_xpm_data
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "data"
--           , argType = TCArray True (-1) (-1) (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Pointer to inline XPM data."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_new_from_xpm_data" gdk_pixbuf_new_from_xpm_data :: 
    Ptr CString ->                          -- data : TCArray True (-1) (-1) (TBasicType TUTF8)
    IO (Ptr Pixbuf)

-- | Creates a new pixbuf by parsing XPM data in memory.
-- 
-- This data is commonly the result of including an XPM file into a
-- program\'s C source.
pixbufNewFromXpmData ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [T.Text]
    -- ^ /@data@/: Pointer to inline XPM data.
    -> m Pixbuf
    -- ^ __Returns:__ A newly-created pixbuf
pixbufNewFromXpmData :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
[Text] -> m Pixbuf
pixbufNewFromXpmData [Text]
data_ = IO Pixbuf -> m Pixbuf
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Pixbuf -> m Pixbuf) -> IO Pixbuf -> m Pixbuf
forall a b. (a -> b) -> a -> b
$ do
    Ptr CString
data_' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
data_
    Ptr Pixbuf
result <- Ptr CString -> IO (Ptr Pixbuf)
gdk_pixbuf_new_from_xpm_data Ptr CString
data_'
    Text -> Ptr Pixbuf -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pixbufNewFromXpmData" Ptr Pixbuf
result
    Pixbuf
result' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
Pixbuf) Ptr Pixbuf
result
    (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
data_'
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
data_'
    Pixbuf -> IO Pixbuf
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Pixbuf::add_alpha
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GdkPixbuf." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "substitute_color"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Whether to set a color to zero opacity."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "r"
--           , argType = TBasicType TUInt8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Red value to substitute."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "g"
--           , argType = TBasicType TUInt8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Green value to substitute."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "b"
--           , argType = TBasicType TUInt8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Blue value to substitute."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_add_alpha" gdk_pixbuf_add_alpha :: 
    Ptr Pixbuf ->                           -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    CInt ->                                 -- substitute_color : TBasicType TBoolean
    Word8 ->                                -- r : TBasicType TUInt8
    Word8 ->                                -- g : TBasicType TUInt8
    Word8 ->                                -- b : TBasicType TUInt8
    IO (Ptr Pixbuf)

-- | Takes an existing pixbuf and adds an alpha channel to it.
-- 
-- If the existing pixbuf already had an alpha channel, the channel
-- values are copied from the original; otherwise, the alpha channel
-- is initialized to 255 (full opacity).
-- 
-- If @substitute_color@ is @TRUE@, then the color specified by the
-- (@r@, @g@, @b@) arguments will be assigned zero opacity. That is,
-- if you pass @(255, 255, 255)@ for the substitute color, all white
-- pixels will become fully transparent.
-- 
-- If @substitute_color@ is @FALSE@, then the (@r@, @g@, @b@) arguments
-- will be ignored.
pixbufAddAlpha ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@pixbuf@/: A t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf'.
    -> Bool
    -- ^ /@substituteColor@/: Whether to set a color to zero opacity.
    -> Word8
    -- ^ /@r@/: Red value to substitute.
    -> Word8
    -- ^ /@g@/: Green value to substitute.
    -> Word8
    -- ^ /@b@/: Blue value to substitute.
    -> m Pixbuf
    -- ^ __Returns:__ A newly-created pixbuf
pixbufAddAlpha :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> Bool -> Word8 -> Word8 -> Word8 -> m Pixbuf
pixbufAddAlpha a
pixbuf Bool
substituteColor Word8
r Word8
g Word8
b = IO Pixbuf -> m Pixbuf
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Pixbuf -> m Pixbuf) -> IO Pixbuf -> m Pixbuf
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    let substituteColor' :: CInt
substituteColor' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
substituteColor
    Ptr Pixbuf
result <- Ptr Pixbuf -> CInt -> Word8 -> Word8 -> Word8 -> IO (Ptr Pixbuf)
gdk_pixbuf_add_alpha Ptr Pixbuf
pixbuf' CInt
substituteColor' Word8
r Word8
g Word8
b
    Text -> Ptr Pixbuf -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pixbufAddAlpha" Ptr Pixbuf
result
    Pixbuf
result' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
Pixbuf) Ptr Pixbuf
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
    Pixbuf -> IO Pixbuf
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result'

#if defined(ENABLE_OVERLOADING)
data PixbufAddAlphaMethodInfo
instance (signature ~ (Bool -> Word8 -> Word8 -> Word8 -> m Pixbuf), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufAddAlphaMethodInfo a signature where
    overloadedMethod = pixbufAddAlpha

instance O.OverloadedMethodInfo PixbufAddAlphaMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufAddAlpha",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufAddAlpha"
        })


#endif

-- method Pixbuf::apply_embedded_orientation
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "src"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pixbuf with an orientation option"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_apply_embedded_orientation" gdk_pixbuf_apply_embedded_orientation :: 
    Ptr Pixbuf ->                           -- src : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    IO (Ptr Pixbuf)

-- | Takes an existing pixbuf and checks for the presence of an
-- associated \"orientation\" option.
-- 
-- The orientation option may be provided by the JPEG loader (which
-- reads the exif orientation tag) or the TIFF loader (which reads
-- the TIFF orientation tag, and compensates it for the partial
-- transforms performed by libtiff).
-- 
-- If an orientation option\/tag is present, the appropriate transform
-- will be performed so that the pixbuf is oriented correctly.
-- 
-- /Since: 2.12/
pixbufApplyEmbeddedOrientation ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@src@/: a pixbuf with an orientation option
    -> m (Maybe Pixbuf)
    -- ^ __Returns:__ A newly-created pixbuf
pixbufApplyEmbeddedOrientation :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> m (Maybe Pixbuf)
pixbufApplyEmbeddedOrientation a
src = IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Pixbuf) -> m (Maybe Pixbuf))
-> IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
src' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
src
    Ptr Pixbuf
result <- Ptr Pixbuf -> IO (Ptr Pixbuf)
gdk_pixbuf_apply_embedded_orientation Ptr Pixbuf
src'
    Maybe Pixbuf
maybeResult <- Ptr Pixbuf -> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Pixbuf
result ((Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf))
-> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ \Ptr Pixbuf
result' -> do
        Pixbuf
result'' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
Pixbuf) Ptr Pixbuf
result'
        Pixbuf -> IO Pixbuf
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
src
    Maybe Pixbuf -> IO (Maybe Pixbuf)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
maybeResult

#if defined(ENABLE_OVERLOADING)
data PixbufApplyEmbeddedOrientationMethodInfo
instance (signature ~ (m (Maybe Pixbuf)), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufApplyEmbeddedOrientationMethodInfo a signature where
    overloadedMethod = pixbufApplyEmbeddedOrientation

instance O.OverloadedMethodInfo PixbufApplyEmbeddedOrientationMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufApplyEmbeddedOrientation",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufApplyEmbeddedOrientation"
        })


#endif

-- method Pixbuf::composite
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "src"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkPixbuf" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the #GdkPixbuf into which to render the results"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest_x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the left coordinate for region to render"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest_y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the top coordinate for region to render"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest_width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the width of the region to render"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest_height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the height of the region to render"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "offset_x"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the offset in the X direction (currently rounded to an integer)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "offset_y"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the offset in the Y direction (currently rounded to an integer)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "scale_x"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the scale factor in the X direction"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "scale_y"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the scale factor in the Y direction"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interp_type"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "InterpType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the interpolation type for the transformation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "overall_alpha"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "overall alpha for source image (0..255)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_composite" gdk_pixbuf_composite :: 
    Ptr Pixbuf ->                           -- src : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    Ptr Pixbuf ->                           -- dest : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    Int32 ->                                -- dest_x : TBasicType TInt
    Int32 ->                                -- dest_y : TBasicType TInt
    Int32 ->                                -- dest_width : TBasicType TInt
    Int32 ->                                -- dest_height : TBasicType TInt
    CDouble ->                              -- offset_x : TBasicType TDouble
    CDouble ->                              -- offset_y : TBasicType TDouble
    CDouble ->                              -- scale_x : TBasicType TDouble
    CDouble ->                              -- scale_y : TBasicType TDouble
    CUInt ->                                -- interp_type : TInterface (Name {namespace = "GdkPixbuf", name = "InterpType"})
    Int32 ->                                -- overall_alpha : TBasicType TInt
    IO ()

-- | Creates a transformation of the source image /@src@/ by scaling by
-- /@scaleX@/ and /@scaleY@/ then translating by /@offsetX@/ and /@offsetY@/.
-- 
-- This gives an image in the coordinates of the destination pixbuf.
-- The rectangle (/@destX@/, /@destY@/, /@destWidth@/, /@destHeight@/)
-- is then alpha blended onto the corresponding rectangle of the
-- original destination image.
-- 
-- When the destination rectangle contains parts not in the source
-- image, the data at the edges of the source image is replicated
-- to infinity.
-- 
-- <<http://developer.gnome.org/gdkpixbuf/stable/composite.png>>
pixbufComposite ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a, IsPixbuf b) =>
    a
    -- ^ /@src@/: a t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf'
    -> b
    -- ^ /@dest@/: the t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf' into which to render the results
    -> Int32
    -- ^ /@destX@/: the left coordinate for region to render
    -> Int32
    -- ^ /@destY@/: the top coordinate for region to render
    -> Int32
    -- ^ /@destWidth@/: the width of the region to render
    -> Int32
    -- ^ /@destHeight@/: the height of the region to render
    -> Double
    -- ^ /@offsetX@/: the offset in the X direction (currently rounded to an integer)
    -> Double
    -- ^ /@offsetY@/: the offset in the Y direction (currently rounded to an integer)
    -> Double
    -- ^ /@scaleX@/: the scale factor in the X direction
    -> Double
    -- ^ /@scaleY@/: the scale factor in the Y direction
    -> GdkPixbuf.Enums.InterpType
    -- ^ /@interpType@/: the interpolation type for the transformation.
    -> Int32
    -- ^ /@overallAlpha@/: overall alpha for source image (0..255)
    -> m ()
pixbufComposite :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPixbuf a, IsPixbuf b) =>
a
-> b
-> Int32
-> Int32
-> Int32
-> Int32
-> Double
-> Double
-> Double
-> Double
-> InterpType
-> Int32
-> m ()
pixbufComposite a
src b
dest Int32
destX Int32
destY Int32
destWidth Int32
destHeight Double
offsetX Double
offsetY Double
scaleX Double
scaleY InterpType
interpType Int32
overallAlpha = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
src' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
src
    Ptr Pixbuf
dest' <- b -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
dest
    let offsetX' :: CDouble
offsetX' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
offsetX
    let offsetY' :: CDouble
offsetY' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
offsetY
    let scaleX' :: CDouble
scaleX' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
scaleX
    let scaleY' :: CDouble
scaleY' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
scaleY
    let interpType' :: CUInt
interpType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (InterpType -> Int) -> InterpType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InterpType -> Int
forall a. Enum a => a -> Int
fromEnum) InterpType
interpType
    Ptr Pixbuf
-> Ptr Pixbuf
-> Int32
-> Int32
-> Int32
-> Int32
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CUInt
-> Int32
-> IO ()
gdk_pixbuf_composite Ptr Pixbuf
src' Ptr Pixbuf
dest' Int32
destX Int32
destY Int32
destWidth Int32
destHeight CDouble
offsetX' CDouble
offsetY' CDouble
scaleX' CDouble
scaleY' CUInt
interpType' Int32
overallAlpha
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
src
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
dest
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PixbufCompositeMethodInfo
instance (signature ~ (b -> Int32 -> Int32 -> Int32 -> Int32 -> Double -> Double -> Double -> Double -> GdkPixbuf.Enums.InterpType -> Int32 -> m ()), MonadIO m, IsPixbuf a, IsPixbuf b) => O.OverloadedMethod PixbufCompositeMethodInfo a signature where
    overloadedMethod = pixbufComposite

instance O.OverloadedMethodInfo PixbufCompositeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufComposite",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufComposite"
        })


#endif

-- method Pixbuf::composite_color
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "src"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkPixbuf" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the #GdkPixbuf into which to render the results"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest_x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the left coordinate for region to render"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest_y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the top coordinate for region to render"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest_width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the width of the region to render"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest_height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the height of the region to render"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "offset_x"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the offset in the X direction (currently rounded to an integer)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "offset_y"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the offset in the Y direction (currently rounded to an integer)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "scale_x"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the scale factor in the X direction"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "scale_y"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the scale factor in the Y direction"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interp_type"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "InterpType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the interpolation type for the transformation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "overall_alpha"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "overall alpha for source image (0..255)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "check_x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the X offset for the checkboard (origin of checkboard is at -@check_x, -@check_y)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "check_y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the Y offset for the checkboard"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "check_size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the size of checks in the checkboard (must be a power of two)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "color1"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the color of check at upper left"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "color2"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the color of the other check"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_composite_color" gdk_pixbuf_composite_color :: 
    Ptr Pixbuf ->                           -- src : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    Ptr Pixbuf ->                           -- dest : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    Int32 ->                                -- dest_x : TBasicType TInt
    Int32 ->                                -- dest_y : TBasicType TInt
    Int32 ->                                -- dest_width : TBasicType TInt
    Int32 ->                                -- dest_height : TBasicType TInt
    CDouble ->                              -- offset_x : TBasicType TDouble
    CDouble ->                              -- offset_y : TBasicType TDouble
    CDouble ->                              -- scale_x : TBasicType TDouble
    CDouble ->                              -- scale_y : TBasicType TDouble
    CUInt ->                                -- interp_type : TInterface (Name {namespace = "GdkPixbuf", name = "InterpType"})
    Int32 ->                                -- overall_alpha : TBasicType TInt
    Int32 ->                                -- check_x : TBasicType TInt
    Int32 ->                                -- check_y : TBasicType TInt
    Int32 ->                                -- check_size : TBasicType TInt
    Word32 ->                               -- color1 : TBasicType TUInt32
    Word32 ->                               -- color2 : TBasicType TUInt32
    IO ()

-- | Creates a transformation of the source image /@src@/ by scaling by
-- /@scaleX@/ and /@scaleY@/ then translating by /@offsetX@/ and /@offsetY@/,
-- then alpha blends the rectangle (/@destX@/ ,/@destY@/, /@destWidth@/,
-- /@destHeight@/) of the resulting image with a checkboard of the
-- colors /@color1@/ and /@color2@/ and renders it onto the destination
-- image.
-- 
-- If the source image has no alpha channel, and /@overallAlpha@/ is 255, a fast
-- path is used which omits the alpha blending and just performs the scaling.
-- 
-- See 'GI.GdkPixbuf.Objects.Pixbuf.pixbufCompositeColorSimple' for a simpler variant of this
-- function suitable for many tasks.
pixbufCompositeColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a, IsPixbuf b) =>
    a
    -- ^ /@src@/: a t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf'
    -> b
    -- ^ /@dest@/: the t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf' into which to render the results
    -> Int32
    -- ^ /@destX@/: the left coordinate for region to render
    -> Int32
    -- ^ /@destY@/: the top coordinate for region to render
    -> Int32
    -- ^ /@destWidth@/: the width of the region to render
    -> Int32
    -- ^ /@destHeight@/: the height of the region to render
    -> Double
    -- ^ /@offsetX@/: the offset in the X direction (currently rounded to an integer)
    -> Double
    -- ^ /@offsetY@/: the offset in the Y direction (currently rounded to an integer)
    -> Double
    -- ^ /@scaleX@/: the scale factor in the X direction
    -> Double
    -- ^ /@scaleY@/: the scale factor in the Y direction
    -> GdkPixbuf.Enums.InterpType
    -- ^ /@interpType@/: the interpolation type for the transformation.
    -> Int32
    -- ^ /@overallAlpha@/: overall alpha for source image (0..255)
    -> Int32
    -- ^ /@checkX@/: the X offset for the checkboard (origin of checkboard is at -/@checkX@/, -/@checkY@/)
    -> Int32
    -- ^ /@checkY@/: the Y offset for the checkboard
    -> Int32
    -- ^ /@checkSize@/: the size of checks in the checkboard (must be a power of two)
    -> Word32
    -- ^ /@color1@/: the color of check at upper left
    -> Word32
    -- ^ /@color2@/: the color of the other check
    -> m ()
pixbufCompositeColor :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPixbuf a, IsPixbuf b) =>
a
-> b
-> Int32
-> Int32
-> Int32
-> Int32
-> Double
-> Double
-> Double
-> Double
-> InterpType
-> Int32
-> Int32
-> Int32
-> Int32
-> Word32
-> Word32
-> m ()
pixbufCompositeColor a
src b
dest Int32
destX Int32
destY Int32
destWidth Int32
destHeight Double
offsetX Double
offsetY Double
scaleX Double
scaleY InterpType
interpType Int32
overallAlpha Int32
checkX Int32
checkY Int32
checkSize Word32
color1 Word32
color2 = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
src' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
src
    Ptr Pixbuf
dest' <- b -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
dest
    let offsetX' :: CDouble
offsetX' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
offsetX
    let offsetY' :: CDouble
offsetY' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
offsetY
    let scaleX' :: CDouble
scaleX' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
scaleX
    let scaleY' :: CDouble
scaleY' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
scaleY
    let interpType' :: CUInt
interpType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (InterpType -> Int) -> InterpType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InterpType -> Int
forall a. Enum a => a -> Int
fromEnum) InterpType
interpType
    Ptr Pixbuf
-> Ptr Pixbuf
-> Int32
-> Int32
-> Int32
-> Int32
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CUInt
-> Int32
-> Int32
-> Int32
-> Int32
-> Word32
-> Word32
-> IO ()
gdk_pixbuf_composite_color Ptr Pixbuf
src' Ptr Pixbuf
dest' Int32
destX Int32
destY Int32
destWidth Int32
destHeight CDouble
offsetX' CDouble
offsetY' CDouble
scaleX' CDouble
scaleY' CUInt
interpType' Int32
overallAlpha Int32
checkX Int32
checkY Int32
checkSize Word32
color1 Word32
color2
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
src
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
dest
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PixbufCompositeColorMethodInfo
instance (signature ~ (b -> Int32 -> Int32 -> Int32 -> Int32 -> Double -> Double -> Double -> Double -> GdkPixbuf.Enums.InterpType -> Int32 -> Int32 -> Int32 -> Int32 -> Word32 -> Word32 -> m ()), MonadIO m, IsPixbuf a, IsPixbuf b) => O.OverloadedMethod PixbufCompositeColorMethodInfo a signature where
    overloadedMethod = pixbufCompositeColor

instance O.OverloadedMethodInfo PixbufCompositeColorMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufCompositeColor",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufCompositeColor"
        })


#endif

-- method Pixbuf::composite_color_simple
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "src"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkPixbuf" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest_width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the width of destination image"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest_height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the height of destination image"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interp_type"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "InterpType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the interpolation type for the transformation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "overall_alpha"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "overall alpha for source image (0..255)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "check_size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the size of checks in the checkboard (must be a power of two)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "color1"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the color of check at upper left"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "color2"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the color of the other check"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_composite_color_simple" gdk_pixbuf_composite_color_simple :: 
    Ptr Pixbuf ->                           -- src : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    Int32 ->                                -- dest_width : TBasicType TInt
    Int32 ->                                -- dest_height : TBasicType TInt
    CUInt ->                                -- interp_type : TInterface (Name {namespace = "GdkPixbuf", name = "InterpType"})
    Int32 ->                                -- overall_alpha : TBasicType TInt
    Int32 ->                                -- check_size : TBasicType TInt
    Word32 ->                               -- color1 : TBasicType TUInt32
    Word32 ->                               -- color2 : TBasicType TUInt32
    IO (Ptr Pixbuf)

-- | Creates a new pixbuf by scaling @src@ to @dest_width@ x @dest_height@
-- and alpha blending the result with a checkboard of colors @color1@
-- and @color2@.
pixbufCompositeColorSimple ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@src@/: a t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf'
    -> Int32
    -- ^ /@destWidth@/: the width of destination image
    -> Int32
    -- ^ /@destHeight@/: the height of destination image
    -> GdkPixbuf.Enums.InterpType
    -- ^ /@interpType@/: the interpolation type for the transformation.
    -> Int32
    -- ^ /@overallAlpha@/: overall alpha for source image (0..255)
    -> Int32
    -- ^ /@checkSize@/: the size of checks in the checkboard (must be a power of two)
    -> Word32
    -- ^ /@color1@/: the color of check at upper left
    -> Word32
    -- ^ /@color2@/: the color of the other check
    -> m (Maybe Pixbuf)
    -- ^ __Returns:__ the new pixbuf
pixbufCompositeColorSimple :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a
-> Int32
-> Int32
-> InterpType
-> Int32
-> Int32
-> Word32
-> Word32
-> m (Maybe Pixbuf)
pixbufCompositeColorSimple a
src Int32
destWidth Int32
destHeight InterpType
interpType Int32
overallAlpha Int32
checkSize Word32
color1 Word32
color2 = IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Pixbuf) -> m (Maybe Pixbuf))
-> IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
src' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
src
    let interpType' :: CUInt
interpType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (InterpType -> Int) -> InterpType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InterpType -> Int
forall a. Enum a => a -> Int
fromEnum) InterpType
interpType
    Ptr Pixbuf
result <- Ptr Pixbuf
-> Int32
-> Int32
-> CUInt
-> Int32
-> Int32
-> Word32
-> Word32
-> IO (Ptr Pixbuf)
gdk_pixbuf_composite_color_simple Ptr Pixbuf
src' Int32
destWidth Int32
destHeight CUInt
interpType' Int32
overallAlpha Int32
checkSize Word32
color1 Word32
color2
    Maybe Pixbuf
maybeResult <- Ptr Pixbuf -> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Pixbuf
result ((Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf))
-> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ \Ptr Pixbuf
result' -> do
        Pixbuf
result'' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
Pixbuf) Ptr Pixbuf
result'
        Pixbuf -> IO Pixbuf
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
src
    Maybe Pixbuf -> IO (Maybe Pixbuf)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
maybeResult

#if defined(ENABLE_OVERLOADING)
data PixbufCompositeColorSimpleMethodInfo
instance (signature ~ (Int32 -> Int32 -> GdkPixbuf.Enums.InterpType -> Int32 -> Int32 -> Word32 -> Word32 -> m (Maybe Pixbuf)), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufCompositeColorSimpleMethodInfo a signature where
    overloadedMethod = pixbufCompositeColorSimple

instance O.OverloadedMethodInfo PixbufCompositeColorSimpleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufCompositeColorSimple",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufCompositeColorSimple"
        })


#endif

-- method Pixbuf::copy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A pixbuf." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_copy" gdk_pixbuf_copy :: 
    Ptr Pixbuf ->                           -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    IO (Ptr Pixbuf)

-- | Creates a new @GdkPixbuf@ with a copy of the information in the specified
-- @pixbuf@.
-- 
-- Note that this does not copy the options set on the original @GdkPixbuf@,
-- use 'GI.GdkPixbuf.Objects.Pixbuf.pixbufCopyOptions' for this.
pixbufCopy ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@pixbuf@/: A pixbuf.
    -> m (Maybe Pixbuf)
    -- ^ __Returns:__ A newly-created pixbuf
pixbufCopy :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> m (Maybe Pixbuf)
pixbufCopy a
pixbuf = IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Pixbuf) -> m (Maybe Pixbuf))
-> IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    Ptr Pixbuf
result <- Ptr Pixbuf -> IO (Ptr Pixbuf)
gdk_pixbuf_copy Ptr Pixbuf
pixbuf'
    Maybe Pixbuf
maybeResult <- Ptr Pixbuf -> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Pixbuf
result ((Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf))
-> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ \Ptr Pixbuf
result' -> do
        Pixbuf
result'' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
Pixbuf) Ptr Pixbuf
result'
        Pixbuf -> IO Pixbuf
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
    Maybe Pixbuf -> IO (Maybe Pixbuf)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
maybeResult

#if defined(ENABLE_OVERLOADING)
data PixbufCopyMethodInfo
instance (signature ~ (m (Maybe Pixbuf)), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufCopyMethodInfo a signature where
    overloadedMethod = pixbufCopy

instance O.OverloadedMethodInfo PixbufCopyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufCopy",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufCopy"
        })


#endif

-- method Pixbuf::copy_area
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "src_pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Source pixbuf." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "src_x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Source X coordinate within @src_pixbuf."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "src_y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Source Y coordinate within @src_pixbuf."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Width of the area to copy."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Height of the area to copy."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest_pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Destination pixbuf."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest_x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "X coordinate within @dest_pixbuf."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest_y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Y coordinate within @dest_pixbuf."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_copy_area" gdk_pixbuf_copy_area :: 
    Ptr Pixbuf ->                           -- src_pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    Int32 ->                                -- src_x : TBasicType TInt
    Int32 ->                                -- src_y : TBasicType TInt
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    Ptr Pixbuf ->                           -- dest_pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    Int32 ->                                -- dest_x : TBasicType TInt
    Int32 ->                                -- dest_y : TBasicType TInt
    IO ()

-- | Copies a rectangular area from @src_pixbuf@ to @dest_pixbuf@.
-- 
-- Conversion of pixbuf formats is done automatically.
-- 
-- If the source rectangle overlaps the destination rectangle on the
-- same pixbuf, it will be overwritten during the copy operation.
-- Therefore, you can not use this function to scroll a pixbuf.
pixbufCopyArea ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a, IsPixbuf b) =>
    a
    -- ^ /@srcPixbuf@/: Source pixbuf.
    -> Int32
    -- ^ /@srcX@/: Source X coordinate within /@srcPixbuf@/.
    -> Int32
    -- ^ /@srcY@/: Source Y coordinate within /@srcPixbuf@/.
    -> Int32
    -- ^ /@width@/: Width of the area to copy.
    -> Int32
    -- ^ /@height@/: Height of the area to copy.
    -> b
    -- ^ /@destPixbuf@/: Destination pixbuf.
    -> Int32
    -- ^ /@destX@/: X coordinate within /@destPixbuf@/.
    -> Int32
    -- ^ /@destY@/: Y coordinate within /@destPixbuf@/.
    -> m ()
pixbufCopyArea :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPixbuf a, IsPixbuf b) =>
a
-> Int32 -> Int32 -> Int32 -> Int32 -> b -> Int32 -> Int32 -> m ()
pixbufCopyArea a
srcPixbuf Int32
srcX Int32
srcY Int32
width Int32
height b
destPixbuf Int32
destX Int32
destY = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
srcPixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
srcPixbuf
    Ptr Pixbuf
destPixbuf' <- b -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
destPixbuf
    Ptr Pixbuf
-> Int32
-> Int32
-> Int32
-> Int32
-> Ptr Pixbuf
-> Int32
-> Int32
-> IO ()
gdk_pixbuf_copy_area Ptr Pixbuf
srcPixbuf' Int32
srcX Int32
srcY Int32
width Int32
height Ptr Pixbuf
destPixbuf' Int32
destX Int32
destY
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
srcPixbuf
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
destPixbuf
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PixbufCopyAreaMethodInfo
instance (signature ~ (Int32 -> Int32 -> Int32 -> Int32 -> b -> Int32 -> Int32 -> m ()), MonadIO m, IsPixbuf a, IsPixbuf b) => O.OverloadedMethod PixbufCopyAreaMethodInfo a signature where
    overloadedMethod = pixbufCopyArea

instance O.OverloadedMethodInfo PixbufCopyAreaMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufCopyArea",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufCopyArea"
        })


#endif

-- method Pixbuf::copy_options
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "src_pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the source pixbuf" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest_pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the destination pixbuf"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_copy_options" gdk_pixbuf_copy_options :: 
    Ptr Pixbuf ->                           -- src_pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    Ptr Pixbuf ->                           -- dest_pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    IO CInt

-- | Copies the key\/value pair options attached to a @GdkPixbuf@ to another
-- @GdkPixbuf@.
-- 
-- This is useful to keep original metadata after having manipulated
-- a file. However be careful to remove metadata which you\'ve already
-- applied, such as the \"orientation\" option after rotating the image.
-- 
-- /Since: 2.36/
pixbufCopyOptions ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a, IsPixbuf b) =>
    a
    -- ^ /@srcPixbuf@/: the source pixbuf
    -> b
    -- ^ /@destPixbuf@/: the destination pixbuf
    -> m Bool
    -- ^ __Returns:__ @TRUE@ on success.
pixbufCopyOptions :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPixbuf a, IsPixbuf b) =>
a -> b -> m Bool
pixbufCopyOptions a
srcPixbuf b
destPixbuf = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
srcPixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
srcPixbuf
    Ptr Pixbuf
destPixbuf' <- b -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
destPixbuf
    CInt
result <- Ptr Pixbuf -> Ptr Pixbuf -> IO CInt
gdk_pixbuf_copy_options Ptr Pixbuf
srcPixbuf' Ptr Pixbuf
destPixbuf'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
srcPixbuf
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
destPixbuf
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data PixbufCopyOptionsMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsPixbuf a, IsPixbuf b) => O.OverloadedMethod PixbufCopyOptionsMethodInfo a signature where
    overloadedMethod = pixbufCopyOptions

instance O.OverloadedMethodInfo PixbufCopyOptionsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufCopyOptions",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufCopyOptions"
        })


#endif

-- method Pixbuf::fill
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkPixbuf`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pixel"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "RGBA pixel to used to clear (`0xffffffff` is opaque white,\n  `0x00000000` transparent black)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_fill" gdk_pixbuf_fill :: 
    Ptr Pixbuf ->                           -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    Word32 ->                               -- pixel : TBasicType TUInt32
    IO ()

-- | Clears a pixbuf to the given RGBA value, converting the RGBA value into
-- the pixbuf\'s pixel format.
-- 
-- The alpha component will be ignored if the pixbuf doesn\'t have an alpha
-- channel.
pixbufFill ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@pixbuf@/: a @GdkPixbuf@
    -> Word32
    -- ^ /@pixel@/: RGBA pixel to used to clear (@0xffffffff@ is opaque white,
    --   @0x00000000@ transparent black)
    -> m ()
pixbufFill :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> Word32 -> m ()
pixbufFill a
pixbuf Word32
pixel = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    Ptr Pixbuf -> Word32 -> IO ()
gdk_pixbuf_fill Ptr Pixbuf
pixbuf' Word32
pixel
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PixbufFillMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufFillMethodInfo a signature where
    overloadedMethod = pixbufFill

instance O.OverloadedMethodInfo PixbufFillMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufFill",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufFill"
        })


#endif

-- method Pixbuf::flip
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "src"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkPixbuf" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "horizontal"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "`TRUE` to flip horizontally, `FALSE` to flip vertically"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_flip" gdk_pixbuf_flip :: 
    Ptr Pixbuf ->                           -- src : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    CInt ->                                 -- horizontal : TBasicType TBoolean
    IO (Ptr Pixbuf)

-- | Flips a pixbuf horizontally or vertically and returns the
-- result in a new pixbuf.
-- 
-- /Since: 2.6/
pixbufFlip ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@src@/: a t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf'
    -> Bool
    -- ^ /@horizontal@/: @TRUE@ to flip horizontally, @FALSE@ to flip vertically
    -> m (Maybe Pixbuf)
    -- ^ __Returns:__ the new pixbuf
pixbufFlip :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> Bool -> m (Maybe Pixbuf)
pixbufFlip a
src Bool
horizontal = IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Pixbuf) -> m (Maybe Pixbuf))
-> IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
src' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
src
    let horizontal' :: CInt
horizontal' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
horizontal
    Ptr Pixbuf
result <- Ptr Pixbuf -> CInt -> IO (Ptr Pixbuf)
gdk_pixbuf_flip Ptr Pixbuf
src' CInt
horizontal'
    Maybe Pixbuf
maybeResult <- Ptr Pixbuf -> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Pixbuf
result ((Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf))
-> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ \Ptr Pixbuf
result' -> do
        Pixbuf
result'' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
Pixbuf) Ptr Pixbuf
result'
        Pixbuf -> IO Pixbuf
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
src
    Maybe Pixbuf -> IO (Maybe Pixbuf)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
maybeResult

#if defined(ENABLE_OVERLOADING)
data PixbufFlipMethodInfo
instance (signature ~ (Bool -> m (Maybe Pixbuf)), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufFlipMethodInfo a signature where
    overloadedMethod = pixbufFlip

instance O.OverloadedMethodInfo PixbufFlipMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufFlip",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufFlip"
        })


#endif

-- method Pixbuf::get_bits_per_sample
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A pixbuf." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_get_bits_per_sample" gdk_pixbuf_get_bits_per_sample :: 
    Ptr Pixbuf ->                           -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    IO Int32

-- | Queries the number of bits per color sample in a pixbuf.
pixbufGetBitsPerSample ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@pixbuf@/: A pixbuf.
    -> m Int32
    -- ^ __Returns:__ Number of bits per color sample.
pixbufGetBitsPerSample :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> m Int32
pixbufGetBitsPerSample a
pixbuf = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    Int32
result <- Ptr Pixbuf -> IO Int32
gdk_pixbuf_get_bits_per_sample Ptr Pixbuf
pixbuf'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data PixbufGetBitsPerSampleMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufGetBitsPerSampleMethodInfo a signature where
    overloadedMethod = pixbufGetBitsPerSample

instance O.OverloadedMethodInfo PixbufGetBitsPerSampleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufGetBitsPerSample",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufGetBitsPerSample"
        })


#endif

-- method Pixbuf::get_byte_length
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A pixbuf" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt64)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_get_byte_length" gdk_pixbuf_get_byte_length :: 
    Ptr Pixbuf ->                           -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    IO Word64

-- | Returns the length of the pixel data, in bytes.
-- 
-- /Since: 2.26/
pixbufGetByteLength ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@pixbuf@/: A pixbuf
    -> m Word64
    -- ^ __Returns:__ The length of the pixel data.
pixbufGetByteLength :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> m Word64
pixbufGetByteLength a
pixbuf = IO Word64 -> m Word64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    Word64
result <- Ptr Pixbuf -> IO Word64
gdk_pixbuf_get_byte_length Ptr Pixbuf
pixbuf'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
    Word64 -> IO Word64
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result

#if defined(ENABLE_OVERLOADING)
data PixbufGetByteLengthMethodInfo
instance (signature ~ (m Word64), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufGetByteLengthMethodInfo a signature where
    overloadedMethod = pixbufGetByteLength

instance O.OverloadedMethodInfo PixbufGetByteLengthMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufGetByteLength",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufGetByteLength"
        })


#endif

-- method Pixbuf::get_colorspace
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A pixbuf." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Colorspace" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_get_colorspace" gdk_pixbuf_get_colorspace :: 
    Ptr Pixbuf ->                           -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    IO CUInt

-- | Queries the color space of a pixbuf.
pixbufGetColorspace ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@pixbuf@/: A pixbuf.
    -> m GdkPixbuf.Enums.Colorspace
    -- ^ __Returns:__ Color space.
pixbufGetColorspace :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> m Colorspace
pixbufGetColorspace a
pixbuf = IO Colorspace -> m Colorspace
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Colorspace -> m Colorspace) -> IO Colorspace -> m Colorspace
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    CUInt
result <- Ptr Pixbuf -> IO CUInt
gdk_pixbuf_get_colorspace Ptr Pixbuf
pixbuf'
    let result' :: Colorspace
result' = (Int -> Colorspace
forall a. Enum a => Int -> a
toEnum (Int -> Colorspace) -> (CUInt -> Int) -> CUInt -> Colorspace
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
    Colorspace -> IO Colorspace
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Colorspace
result'

#if defined(ENABLE_OVERLOADING)
data PixbufGetColorspaceMethodInfo
instance (signature ~ (m GdkPixbuf.Enums.Colorspace), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufGetColorspaceMethodInfo a signature where
    overloadedMethod = pixbufGetColorspace

instance O.OverloadedMethodInfo PixbufGetColorspaceMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufGetColorspace",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufGetColorspace"
        })


#endif

-- method Pixbuf::get_has_alpha
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A pixbuf." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_get_has_alpha" gdk_pixbuf_get_has_alpha :: 
    Ptr Pixbuf ->                           -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    IO CInt

-- | Queries whether a pixbuf has an alpha channel (opacity information).
pixbufGetHasAlpha ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@pixbuf@/: A pixbuf.
    -> m Bool
    -- ^ __Returns:__ @TRUE@ if it has an alpha channel, @FALSE@ otherwise.
pixbufGetHasAlpha :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> m Bool
pixbufGetHasAlpha a
pixbuf = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    CInt
result <- Ptr Pixbuf -> IO CInt
gdk_pixbuf_get_has_alpha Ptr Pixbuf
pixbuf'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data PixbufGetHasAlphaMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufGetHasAlphaMethodInfo a signature where
    overloadedMethod = pixbufGetHasAlpha

instance O.OverloadedMethodInfo PixbufGetHasAlphaMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufGetHasAlpha",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufGetHasAlpha"
        })


#endif

-- method Pixbuf::get_height
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A pixbuf." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_get_height" gdk_pixbuf_get_height :: 
    Ptr Pixbuf ->                           -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    IO Int32

-- | Queries the height of a pixbuf.
pixbufGetHeight ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@pixbuf@/: A pixbuf.
    -> m Int32
    -- ^ __Returns:__ Height in pixels.
pixbufGetHeight :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> m Int32
pixbufGetHeight a
pixbuf = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    Int32
result <- Ptr Pixbuf -> IO Int32
gdk_pixbuf_get_height Ptr Pixbuf
pixbuf'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data PixbufGetHeightMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufGetHeightMethodInfo a signature where
    overloadedMethod = pixbufGetHeight

instance O.OverloadedMethodInfo PixbufGetHeightMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufGetHeight",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufGetHeight"
        })


#endif

-- method Pixbuf::get_n_channels
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A pixbuf." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_get_n_channels" gdk_pixbuf_get_n_channels :: 
    Ptr Pixbuf ->                           -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    IO Int32

-- | Queries the number of channels of a pixbuf.
pixbufGetNChannels ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@pixbuf@/: A pixbuf.
    -> m Int32
    -- ^ __Returns:__ Number of channels.
pixbufGetNChannels :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> m Int32
pixbufGetNChannels a
pixbuf = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    Int32
result <- Ptr Pixbuf -> IO Int32
gdk_pixbuf_get_n_channels Ptr Pixbuf
pixbuf'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data PixbufGetNChannelsMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufGetNChannelsMethodInfo a signature where
    overloadedMethod = pixbufGetNChannels

instance O.OverloadedMethodInfo PixbufGetNChannelsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufGetNChannels",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufGetNChannels"
        })


#endif

-- method Pixbuf::get_option
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkPixbuf`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a nul-terminated string."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_get_option" gdk_pixbuf_get_option :: 
    Ptr Pixbuf ->                           -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    CString ->                              -- key : TBasicType TUTF8
    IO CString

-- | Looks up /@key@/ in the list of options that may have been attached to the
-- /@pixbuf@/ when it was loaded, or that may have been attached by another
-- function using 'GI.GdkPixbuf.Objects.Pixbuf.pixbufSetOption'.
-- 
-- For instance, the ANI loader provides \"Title\" and \"Artist\" options.
-- The ICO, XBM, and XPM loaders provide \"x_hot\" and \"y_hot\" hot-spot
-- options for cursor definitions. The PNG loader provides the tEXt ancillary
-- chunk key\/value pairs as options. Since 2.12, the TIFF and JPEG loaders
-- return an \"orientation\" option string that corresponds to the embedded
-- TIFF\/Exif orientation tag (if present). Since 2.32, the TIFF loader sets
-- the \"multipage\" option string to \"yes\" when a multi-page TIFF is loaded.
-- Since 2.32 the JPEG and PNG loaders set \"x-dpi\" and \"y-dpi\" if the file
-- contains image density information in dots per inch.
-- Since 2.36.6, the JPEG loader sets the \"comment\" option with the comment
-- EXIF tag.
pixbufGetOption ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@pixbuf@/: a @GdkPixbuf@
    -> T.Text
    -- ^ /@key@/: a nul-terminated string.
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the value associated with @key@
pixbufGetOption :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> Text -> m (Maybe Text)
pixbufGetOption a
pixbuf Text
key = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    CString
key' <- Text -> IO CString
textToCString Text
key
    CString
result <- Ptr Pixbuf -> CString -> IO CString
gdk_pixbuf_get_option Ptr Pixbuf
pixbuf' CString
key'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data PixbufGetOptionMethodInfo
instance (signature ~ (T.Text -> m (Maybe T.Text)), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufGetOptionMethodInfo a signature where
    overloadedMethod = pixbufGetOption

instance O.OverloadedMethodInfo PixbufGetOptionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufGetOption",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufGetOption"
        })


#endif

-- XXX Could not generate method Pixbuf::get_options
-- Not implemented: Hash table argument with transfer = Container? result
#if defined(ENABLE_OVERLOADING)
-- XXX: Dummy instance, since code generation failed.
-- Please file a bug at http://github.com/haskell-gi/haskell-gi.
data PixbufGetOptionsMethodInfo
instance (p ~ (), o ~ O.UnsupportedMethodError "getOptions" Pixbuf) => O.OverloadedMethod PixbufGetOptionsMethodInfo o p where
    overloadedMethod = undefined

instance (o ~ O.UnsupportedMethodError "getOptions" Pixbuf) => O.OverloadedMethodInfo PixbufGetOptionsMethodInfo o where
    overloadedMethodInfo = undefined

#endif

-- method Pixbuf::get_pixels
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A pixbuf." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TUInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of the binary data."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "length"
--              , argType = TBasicType TUInt
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "The length of the binary data."
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just (TCArray False (-1) 1 (TBasicType TUInt8))
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_get_pixels_with_length" gdk_pixbuf_get_pixels_with_length :: 
    Ptr Pixbuf ->                           -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    Ptr Word32 ->                           -- length : TBasicType TUInt
    IO (Ptr Word8)

-- | Queries a pointer to the pixel data of a pixbuf.
-- 
-- This function will cause an implicit copy of the pixbuf data if the
-- pixbuf was created from read-only data.
-- 
-- Please see the section on <http://developer.gnome.org/gdkpixbuf/stable/class.Pixbuf.html#image-data image data> for information
-- about how the pixel data is stored in memory.
-- 
-- /Since: 2.26/
pixbufGetPixels ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@pixbuf@/: A pixbuf.
    -> m ByteString
    -- ^ __Returns:__ A pointer to the pixbuf\'s
    -- pixel data.
pixbufGetPixels :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> m ByteString
pixbufGetPixels a
pixbuf = IO ByteString -> m ByteString
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteString -> m ByteString) -> IO ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    Ptr Word32
length_ <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
    Ptr Word8
result <- Ptr Pixbuf -> Ptr Word32 -> IO (Ptr Word8)
gdk_pixbuf_get_pixels_with_length Ptr Pixbuf
pixbuf' Ptr Word32
length_
    Word32
length_' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
length_
    Text -> PixbufDestroyNotify
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pixbufGetPixels" Ptr Word8
result
    ByteString
result' <- (Word32 -> Ptr Word8 -> IO ByteString
forall a. Integral a => a -> Ptr Word8 -> IO ByteString
unpackByteStringWithLength Word32
length_') Ptr Word8
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
    Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
length_
    ByteString -> IO ByteString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
result'

#if defined(ENABLE_OVERLOADING)
data PixbufGetPixelsMethodInfo
instance (signature ~ (m ByteString), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufGetPixelsMethodInfo a signature where
    overloadedMethod = pixbufGetPixels

instance O.OverloadedMethodInfo PixbufGetPixelsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufGetPixels",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufGetPixels"
        })


#endif

-- method Pixbuf::get_rowstride
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A pixbuf." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_get_rowstride" gdk_pixbuf_get_rowstride :: 
    Ptr Pixbuf ->                           -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    IO Int32

-- | Queries the rowstride of a pixbuf, which is the number of bytes between
-- the start of a row and the start of the next row.
pixbufGetRowstride ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@pixbuf@/: A pixbuf.
    -> m Int32
    -- ^ __Returns:__ Distance between row starts.
pixbufGetRowstride :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> m Int32
pixbufGetRowstride a
pixbuf = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    Int32
result <- Ptr Pixbuf -> IO Int32
gdk_pixbuf_get_rowstride Ptr Pixbuf
pixbuf'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data PixbufGetRowstrideMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufGetRowstrideMethodInfo a signature where
    overloadedMethod = pixbufGetRowstride

instance O.OverloadedMethodInfo PixbufGetRowstrideMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufGetRowstride",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufGetRowstride"
        })


#endif

-- method Pixbuf::get_width
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A pixbuf." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_get_width" gdk_pixbuf_get_width :: 
    Ptr Pixbuf ->                           -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    IO Int32

-- | Queries the width of a pixbuf.
pixbufGetWidth ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@pixbuf@/: A pixbuf.
    -> m Int32
    -- ^ __Returns:__ Width in pixels.
pixbufGetWidth :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> m Int32
pixbufGetWidth a
pixbuf = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    Int32
result <- Ptr Pixbuf -> IO Int32
gdk_pixbuf_get_width Ptr Pixbuf
pixbuf'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data PixbufGetWidthMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufGetWidthMethodInfo a signature where
    overloadedMethod = pixbufGetWidth

instance O.OverloadedMethodInfo PixbufGetWidthMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufGetWidth",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufGetWidth"
        })


#endif

-- method Pixbuf::new_subpixbuf
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "src_pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkPixbuf`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "src_x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "X coord in @src_pixbuf"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "src_y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Y coord in @src_pixbuf"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "width of region in @src_pixbuf"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "height of region in @src_pixbuf"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_new_subpixbuf" gdk_pixbuf_new_subpixbuf :: 
    Ptr Pixbuf ->                           -- src_pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    Int32 ->                                -- src_x : TBasicType TInt
    Int32 ->                                -- src_y : TBasicType TInt
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    IO (Ptr Pixbuf)

-- | Creates a new pixbuf which represents a sub-region of @src_pixbuf@.
-- 
-- The new pixbuf shares its pixels with the original pixbuf, so
-- writing to one affects both.  The new pixbuf holds a reference to
-- @src_pixbuf@, so @src_pixbuf@ will not be finalized until the new
-- pixbuf is finalized.
-- 
-- Note that if @src_pixbuf@ is read-only, this function will force it
-- to be mutable.
pixbufNewSubpixbuf ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@srcPixbuf@/: a @GdkPixbuf@
    -> Int32
    -- ^ /@srcX@/: X coord in /@srcPixbuf@/
    -> Int32
    -- ^ /@srcY@/: Y coord in /@srcPixbuf@/
    -> Int32
    -- ^ /@width@/: width of region in /@srcPixbuf@/
    -> Int32
    -- ^ /@height@/: height of region in /@srcPixbuf@/
    -> m Pixbuf
    -- ^ __Returns:__ a new pixbuf
pixbufNewSubpixbuf :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> Int32 -> Int32 -> Int32 -> Int32 -> m Pixbuf
pixbufNewSubpixbuf a
srcPixbuf Int32
srcX Int32
srcY Int32
width Int32
height = IO Pixbuf -> m Pixbuf
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Pixbuf -> m Pixbuf) -> IO Pixbuf -> m Pixbuf
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
srcPixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
srcPixbuf
    Ptr Pixbuf
result <- Ptr Pixbuf -> Int32 -> Int32 -> Int32 -> Int32 -> IO (Ptr Pixbuf)
gdk_pixbuf_new_subpixbuf Ptr Pixbuf
srcPixbuf' Int32
srcX Int32
srcY Int32
width Int32
height
    Text -> Ptr Pixbuf -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pixbufNewSubpixbuf" Ptr Pixbuf
result
    Pixbuf
result' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
Pixbuf) Ptr Pixbuf
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
srcPixbuf
    Pixbuf -> IO Pixbuf
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result'

#if defined(ENABLE_OVERLOADING)
data PixbufNewSubpixbufMethodInfo
instance (signature ~ (Int32 -> Int32 -> Int32 -> Int32 -> m Pixbuf), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufNewSubpixbufMethodInfo a signature where
    overloadedMethod = pixbufNewSubpixbuf

instance O.OverloadedMethodInfo PixbufNewSubpixbufMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufNewSubpixbuf",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufNewSubpixbuf"
        })


#endif

-- method Pixbuf::read_pixel_bytes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A pixbuf" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "Bytes" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_read_pixel_bytes" gdk_pixbuf_read_pixel_bytes :: 
    Ptr Pixbuf ->                           -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    IO (Ptr GLib.Bytes.Bytes)

-- | Provides a t'GI.GLib.Structs.Bytes.Bytes' buffer containing the raw pixel data; the data
-- must not be modified.
-- 
-- This function allows skipping the implicit copy that must be made
-- if @/gdk_pixbuf_get_pixels()/@ is called on a read-only pixbuf.
-- 
-- /Since: 2.32/
pixbufReadPixelBytes ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@pixbuf@/: A pixbuf
    -> m GLib.Bytes.Bytes
    -- ^ __Returns:__ A new reference to a read-only copy of
    --   the pixel data.  Note that for mutable pixbufs, this function will
    --   incur a one-time copy of the pixel data for conversion into the
    --   returned t'GI.GLib.Structs.Bytes.Bytes'.
pixbufReadPixelBytes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> m Bytes
pixbufReadPixelBytes a
pixbuf = IO Bytes -> m Bytes
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bytes -> m Bytes) -> IO Bytes -> m Bytes
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    Ptr Bytes
result <- Ptr Pixbuf -> IO (Ptr Bytes)
gdk_pixbuf_read_pixel_bytes Ptr Pixbuf
pixbuf'
    Text -> Ptr Bytes -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pixbufReadPixelBytes" Ptr Bytes
result
    Bytes
result' <- ((ManagedPtr Bytes -> Bytes) -> Ptr Bytes -> IO Bytes
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Bytes -> Bytes
GLib.Bytes.Bytes) Ptr Bytes
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
    Bytes -> IO Bytes
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bytes
result'

#if defined(ENABLE_OVERLOADING)
data PixbufReadPixelBytesMethodInfo
instance (signature ~ (m GLib.Bytes.Bytes), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufReadPixelBytesMethodInfo a signature where
    overloadedMethod = pixbufReadPixelBytes

instance O.OverloadedMethodInfo PixbufReadPixelBytesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufReadPixelBytes",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufReadPixelBytes"
        })


#endif

-- method Pixbuf::read_pixels
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A pixbuf" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt8)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_read_pixels" gdk_pixbuf_read_pixels :: 
    Ptr Pixbuf ->                           -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    IO Word8

-- | Provides a read-only pointer to the raw pixel data.
-- 
-- This function allows skipping the implicit copy that must be made
-- if @/gdk_pixbuf_get_pixels()/@ is called on a read-only pixbuf.
-- 
-- /Since: 2.32/
pixbufReadPixels ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@pixbuf@/: A pixbuf
    -> m Word8
    -- ^ __Returns:__ a read-only pointer to the raw pixel data
pixbufReadPixels :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> m Word8
pixbufReadPixels a
pixbuf = IO Word8 -> m Word8
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word8 -> m Word8) -> IO Word8 -> m Word8
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    Word8
result <- Ptr Pixbuf -> IO Word8
gdk_pixbuf_read_pixels Ptr Pixbuf
pixbuf'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
    Word8 -> IO Word8
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word8
result

#if defined(ENABLE_OVERLOADING)
data PixbufReadPixelsMethodInfo
instance (signature ~ (m Word8), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufReadPixelsMethodInfo a signature where
    overloadedMethod = pixbufReadPixels

instance O.OverloadedMethodInfo PixbufReadPixelsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufReadPixels",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufReadPixels"
        })


#endif

-- method Pixbuf::remove_option
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkPixbuf`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a nul-terminated string representing the key to remove."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_remove_option" gdk_pixbuf_remove_option :: 
    Ptr Pixbuf ->                           -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    CString ->                              -- key : TBasicType TUTF8
    IO CInt

-- | Removes the key\/value pair option attached to a @GdkPixbuf@.
-- 
-- /Since: 2.36/
pixbufRemoveOption ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@pixbuf@/: a @GdkPixbuf@
    -> T.Text
    -- ^ /@key@/: a nul-terminated string representing the key to remove.
    -> m Bool
    -- ^ __Returns:__ @TRUE@ if an option was removed, @FALSE@ if not.
pixbufRemoveOption :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> Text -> m Bool
pixbufRemoveOption a
pixbuf Text
key = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    CString
key' <- Text -> IO CString
textToCString Text
key
    CInt
result <- Ptr Pixbuf -> CString -> IO CInt
gdk_pixbuf_remove_option Ptr Pixbuf
pixbuf' CString
key'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data PixbufRemoveOptionMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufRemoveOptionMethodInfo a signature where
    overloadedMethod = pixbufRemoveOption

instance O.OverloadedMethodInfo PixbufRemoveOptionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufRemoveOption",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufRemoveOption"
        })


#endif

-- method Pixbuf::rotate_simple
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "src"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkPixbuf" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "angle"
--           , argType =
--               TInterface
--                 Name { namespace = "GdkPixbuf" , name = "PixbufRotation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the angle to rotate by"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_rotate_simple" gdk_pixbuf_rotate_simple :: 
    Ptr Pixbuf ->                           -- src : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    CUInt ->                                -- angle : TInterface (Name {namespace = "GdkPixbuf", name = "PixbufRotation"})
    IO (Ptr Pixbuf)

-- | Rotates a pixbuf by a multiple of 90 degrees, and returns the
-- result in a new pixbuf.
-- 
-- If @angle@ is 0, this function will return a copy of @src@.
-- 
-- /Since: 2.6/
pixbufRotateSimple ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@src@/: a t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf'
    -> GdkPixbuf.Enums.PixbufRotation
    -- ^ /@angle@/: the angle to rotate by
    -> m (Maybe Pixbuf)
    -- ^ __Returns:__ the new pixbuf
pixbufRotateSimple :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> PixbufRotation -> m (Maybe Pixbuf)
pixbufRotateSimple a
src PixbufRotation
angle = IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Pixbuf) -> m (Maybe Pixbuf))
-> IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
src' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
src
    let angle' :: CUInt
angle' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (PixbufRotation -> Int) -> PixbufRotation -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PixbufRotation -> Int
forall a. Enum a => a -> Int
fromEnum) PixbufRotation
angle
    Ptr Pixbuf
result <- Ptr Pixbuf -> CUInt -> IO (Ptr Pixbuf)
gdk_pixbuf_rotate_simple Ptr Pixbuf
src' CUInt
angle'
    Maybe Pixbuf
maybeResult <- Ptr Pixbuf -> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Pixbuf
result ((Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf))
-> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ \Ptr Pixbuf
result' -> do
        Pixbuf
result'' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
Pixbuf) Ptr Pixbuf
result'
        Pixbuf -> IO Pixbuf
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
src
    Maybe Pixbuf -> IO (Maybe Pixbuf)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
maybeResult

#if defined(ENABLE_OVERLOADING)
data PixbufRotateSimpleMethodInfo
instance (signature ~ (GdkPixbuf.Enums.PixbufRotation -> m (Maybe Pixbuf)), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufRotateSimpleMethodInfo a signature where
    overloadedMethod = pixbufRotateSimple

instance O.OverloadedMethodInfo PixbufRotateSimpleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufRotateSimple",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufRotateSimple"
        })


#endif

-- method Pixbuf::saturate_and_pixelate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "src"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "source image" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "place to write modified version of @src"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "saturation"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "saturation factor" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pixelate"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether to pixelate"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_saturate_and_pixelate" gdk_pixbuf_saturate_and_pixelate :: 
    Ptr Pixbuf ->                           -- src : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    Ptr Pixbuf ->                           -- dest : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    CFloat ->                               -- saturation : TBasicType TFloat
    CInt ->                                 -- pixelate : TBasicType TBoolean
    IO ()

-- | Modifies saturation and optionally pixelates @src@, placing the result in
-- @dest@.
-- 
-- The @src@ and @dest@ pixbufs must have the same image format, size, and
-- rowstride.
-- 
-- The @src@ and @dest@ arguments may be the same pixbuf with no ill effects.
-- 
-- If @saturation@ is 1.0 then saturation is not changed. If it\'s less than 1.0,
-- saturation is reduced (the image turns toward grayscale); if greater than
-- 1.0, saturation is increased (the image gets more vivid colors).
-- 
-- If @pixelate@ is @TRUE@, then pixels are faded in a checkerboard pattern to
-- create a pixelated image.
pixbufSaturateAndPixelate ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a, IsPixbuf b) =>
    a
    -- ^ /@src@/: source image
    -> b
    -- ^ /@dest@/: place to write modified version of /@src@/
    -> Float
    -- ^ /@saturation@/: saturation factor
    -> Bool
    -- ^ /@pixelate@/: whether to pixelate
    -> m ()
pixbufSaturateAndPixelate :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPixbuf a, IsPixbuf b) =>
a -> b -> Float -> Bool -> m ()
pixbufSaturateAndPixelate a
src b
dest Float
saturation Bool
pixelate = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
src' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
src
    Ptr Pixbuf
dest' <- b -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
dest
    let saturation' :: CFloat
saturation' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
saturation
    let pixelate' :: CInt
pixelate' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
pixelate
    Ptr Pixbuf -> Ptr Pixbuf -> CFloat -> CInt -> IO ()
gdk_pixbuf_saturate_and_pixelate Ptr Pixbuf
src' Ptr Pixbuf
dest' CFloat
saturation' CInt
pixelate'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
src
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
dest
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PixbufSaturateAndPixelateMethodInfo
instance (signature ~ (b -> Float -> Bool -> m ()), MonadIO m, IsPixbuf a, IsPixbuf b) => O.OverloadedMethod PixbufSaturateAndPixelateMethodInfo a signature where
    overloadedMethod = pixbufSaturateAndPixelate

instance O.OverloadedMethodInfo PixbufSaturateAndPixelateMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufSaturateAndPixelate",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufSaturateAndPixelate"
        })


#endif

-- method Pixbuf::save_to_bufferv
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkPixbuf`." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "buffer"
--           , argType = TCArray False (-1) 2 (TBasicType TUInt8)
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "\n  location to receive a pointer to the new buffer."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "buffer_size"
--           , argType = TBasicType TUInt64
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "location to receive the size of the new buffer."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "type"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "name of file format."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "option_keys"
--           , argType = TCArray True (-1) (-1) (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "name of options to set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "option_values"
--           , argType = TCArray True (-1) (-1) (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "values for named options"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "buffer_size"
--              , argType = TBasicType TUInt64
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just "location to receive the size of the new buffer."
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "gdk_pixbuf_save_to_bufferv" gdk_pixbuf_save_to_bufferv :: 
    Ptr Pixbuf ->                           -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    Ptr (Ptr Word8) ->                      -- buffer : TCArray False (-1) 2 (TBasicType TUInt8)
    Ptr Word64 ->                           -- buffer_size : TBasicType TUInt64
    CString ->                              -- type : TBasicType TUTF8
    Ptr CString ->                          -- option_keys : TCArray True (-1) (-1) (TBasicType TUTF8)
    Ptr CString ->                          -- option_values : TCArray True (-1) (-1) (TBasicType TUTF8)
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Vector version of @gdk_pixbuf_save_to_buffer()@.
-- 
-- Saves pixbuf to a new buffer in format /@type@/, which is currently \"jpeg\",
-- \"tiff\", \"png\", \"ico\" or \"bmp\".
-- 
-- See t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf'.@/save_to_buffer/@() for more details.
-- 
-- /Since: 2.4/
pixbufSaveToBufferv ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@pixbuf@/: a @GdkPixbuf@.
    -> T.Text
    -- ^ /@type@/: name of file format.
    -> Maybe ([T.Text])
    -- ^ /@optionKeys@/: name of options to set
    -> Maybe ([T.Text])
    -- ^ /@optionValues@/: values for named options
    -> m (ByteString)
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
pixbufSaveToBufferv :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> Text -> Maybe [Text] -> Maybe [Text] -> m ByteString
pixbufSaveToBufferv a
pixbuf Text
type_ Maybe [Text]
optionKeys Maybe [Text]
optionValues = IO ByteString -> m ByteString
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteString -> m ByteString) -> IO ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    Ptr (Ptr Word8)
buffer <- IO (Ptr (Ptr Word8))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr Word8))
    Ptr Word64
bufferSize <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
    CString
type_' <- Text -> IO CString
textToCString Text
type_
    Ptr CString
maybeOptionKeys <- case Maybe [Text]
optionKeys of
        Maybe [Text]
Nothing -> Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
forall a. Ptr a
nullPtr
        Just [Text]
jOptionKeys -> do
            Ptr CString
jOptionKeys' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
jOptionKeys
            Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
jOptionKeys'
    Ptr CString
maybeOptionValues <- case Maybe [Text]
optionValues of
        Maybe [Text]
Nothing -> Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
forall a. Ptr a
nullPtr
        Just [Text]
jOptionValues -> do
            Ptr CString
jOptionValues' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
jOptionValues
            Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
jOptionValues'
    IO ByteString -> IO () -> IO ByteString
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Pixbuf
-> Ptr (Ptr Word8)
-> Ptr Word64
-> CString
-> Ptr CString
-> Ptr CString
-> Ptr (Ptr GError)
-> IO CInt
gdk_pixbuf_save_to_bufferv Ptr Pixbuf
pixbuf' Ptr (Ptr Word8)
buffer Ptr Word64
bufferSize CString
type_' Ptr CString
maybeOptionKeys Ptr CString
maybeOptionValues
        Word64
bufferSize' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
bufferSize
        Ptr Word8
buffer' <- Ptr (Ptr Word8) -> IO (Ptr Word8)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr Word8)
buffer
        ByteString
buffer'' <- (Word64 -> Ptr Word8 -> IO ByteString
forall a. Integral a => a -> Ptr Word8 -> IO ByteString
unpackByteStringWithLength Word64
bufferSize') Ptr Word8
buffer'
        PixbufDestroyNotify
forall a. Ptr a -> IO ()
freeMem Ptr Word8
buffer'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
        Ptr (Ptr Word8) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Word8)
buffer
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
bufferSize
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
type_'
        (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionKeys
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionKeys
        (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionValues
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionValues
        ByteString -> IO ByteString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
buffer''
     ) (do
        Ptr (Ptr Word8) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Word8)
buffer
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
bufferSize
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
type_'
        (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionKeys
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionKeys
        (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionValues
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionValues
     )

#if defined(ENABLE_OVERLOADING)
data PixbufSaveToBuffervMethodInfo
instance (signature ~ (T.Text -> Maybe ([T.Text]) -> Maybe ([T.Text]) -> m (ByteString)), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufSaveToBuffervMethodInfo a signature where
    overloadedMethod = pixbufSaveToBufferv

instance O.OverloadedMethodInfo PixbufSaveToBuffervMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufSaveToBufferv",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufSaveToBufferv"
        })


#endif

-- method Pixbuf::save_to_callbackv
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkPixbuf`." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "save_func"
--           , argType =
--               TInterface
--                 Name { namespace = "GdkPixbuf" , name = "PixbufSaveFunc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a function that is called to save each block of data that\n  the save routine generates."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeCall
--           , argClosure = 2
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data to pass to the save function."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "name of file format."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "option_keys"
--           , argType = TCArray True (-1) (-1) (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "name of options to set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "option_values"
--           , argType = TCArray True (-1) (-1) (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "values for named options"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "gdk_pixbuf_save_to_callbackv" gdk_pixbuf_save_to_callbackv :: 
    Ptr Pixbuf ->                           -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    FunPtr GdkPixbuf.Callbacks.C_PixbufSaveFunc -> -- save_func : TInterface (Name {namespace = "GdkPixbuf", name = "PixbufSaveFunc"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    CString ->                              -- type : TBasicType TUTF8
    Ptr CString ->                          -- option_keys : TCArray True (-1) (-1) (TBasicType TUTF8)
    Ptr CString ->                          -- option_values : TCArray True (-1) (-1) (TBasicType TUTF8)
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Vector version of @gdk_pixbuf_save_to_callback()@.
-- 
-- Saves pixbuf to a callback in format /@type@/, which is currently \"jpeg\",
-- \"png\", \"tiff\", \"ico\" or \"bmp\".
-- 
-- If /@error@/ is set, @FALSE@ will be returned.
-- 
-- See t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf'.@/save_to_callback/@() for more details.
-- 
-- /Since: 2.4/
pixbufSaveToCallbackv ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@pixbuf@/: a @GdkPixbuf@.
    -> GdkPixbuf.Callbacks.PixbufSaveFunc
    -- ^ /@saveFunc@/: a function that is called to save each block of data that
    --   the save routine generates.
    -> T.Text
    -- ^ /@type@/: name of file format.
    -> Maybe ([T.Text])
    -- ^ /@optionKeys@/: name of options to set
    -> Maybe ([T.Text])
    -- ^ /@optionValues@/: values for named options
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
pixbufSaveToCallbackv :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> PixbufSaveFunc -> Text -> Maybe [Text] -> Maybe [Text] -> m ()
pixbufSaveToCallbackv a
pixbuf PixbufSaveFunc
saveFunc Text
type_ Maybe [Text]
optionKeys Maybe [Text]
optionValues = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    FunPtr C_PixbufSaveFunc
saveFunc' <- C_PixbufSaveFunc -> IO (FunPtr C_PixbufSaveFunc)
GdkPixbuf.Callbacks.mk_PixbufSaveFunc (Maybe (Ptr (FunPtr C_PixbufSaveFunc))
-> PixbufSaveFunc_WithClosures -> C_PixbufSaveFunc
GdkPixbuf.Callbacks.wrap_PixbufSaveFunc Maybe (Ptr (FunPtr C_PixbufSaveFunc))
forall a. Maybe a
Nothing (PixbufSaveFunc -> PixbufSaveFunc_WithClosures
GdkPixbuf.Callbacks.drop_closures_PixbufSaveFunc PixbufSaveFunc
saveFunc))
    CString
type_' <- Text -> IO CString
textToCString Text
type_
    Ptr CString
maybeOptionKeys <- case Maybe [Text]
optionKeys of
        Maybe [Text]
Nothing -> Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
forall a. Ptr a
nullPtr
        Just [Text]
jOptionKeys -> do
            Ptr CString
jOptionKeys' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
jOptionKeys
            Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
jOptionKeys'
    Ptr CString
maybeOptionValues <- case Maybe [Text]
optionValues of
        Maybe [Text]
Nothing -> Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
forall a. Ptr a
nullPtr
        Just [Text]
jOptionValues -> do
            Ptr CString
jOptionValues' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
jOptionValues
            Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
jOptionValues'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Pixbuf
-> FunPtr C_PixbufSaveFunc
-> Ptr ()
-> CString
-> Ptr CString
-> Ptr CString
-> Ptr (Ptr GError)
-> IO CInt
gdk_pixbuf_save_to_callbackv Ptr Pixbuf
pixbuf' FunPtr C_PixbufSaveFunc
saveFunc' Ptr ()
forall a. Ptr a
userData CString
type_' Ptr CString
maybeOptionKeys Ptr CString
maybeOptionValues
        Ptr Any -> IO ()
forall a. Ptr a -> IO ()
safeFreeFunPtr (Ptr Any -> IO ()) -> Ptr Any -> IO ()
forall a b. (a -> b) -> a -> b
$ FunPtr C_PixbufSaveFunc -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_PixbufSaveFunc
saveFunc'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
type_'
        (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionKeys
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionKeys
        (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionValues
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionValues
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        Ptr Any -> IO ()
forall a. Ptr a -> IO ()
safeFreeFunPtr (Ptr Any -> IO ()) -> Ptr Any -> IO ()
forall a b. (a -> b) -> a -> b
$ FunPtr C_PixbufSaveFunc -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_PixbufSaveFunc
saveFunc'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
type_'
        (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionKeys
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionKeys
        (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionValues
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionValues
     )

#if defined(ENABLE_OVERLOADING)
data PixbufSaveToCallbackvMethodInfo
instance (signature ~ (GdkPixbuf.Callbacks.PixbufSaveFunc -> T.Text -> Maybe ([T.Text]) -> Maybe ([T.Text]) -> m ()), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufSaveToCallbackvMethodInfo a signature where
    overloadedMethod = pixbufSaveToCallbackv

instance O.OverloadedMethodInfo PixbufSaveToCallbackvMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufSaveToCallbackv",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufSaveToCallbackv"
        })


#endif

-- method Pixbuf::save_to_streamv
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkPixbuf`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "stream"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "OutputStream" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GOutputStream` to save the pixbuf to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "name of file format"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "option_keys"
--           , argType = TCArray True (-1) (-1) (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "name of options to set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "option_values"
--           , argType = TCArray True (-1) (-1) (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "values for named options"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "optional `GCancellable` object, `NULL` to ignore"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "gdk_pixbuf_save_to_streamv" gdk_pixbuf_save_to_streamv :: 
    Ptr Pixbuf ->                           -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    Ptr Gio.OutputStream.OutputStream ->    -- stream : TInterface (Name {namespace = "Gio", name = "OutputStream"})
    CString ->                              -- type : TBasicType TUTF8
    Ptr CString ->                          -- option_keys : TCArray True (-1) (-1) (TBasicType TUTF8)
    Ptr CString ->                          -- option_values : TCArray True (-1) (-1) (TBasicType TUTF8)
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Saves @pixbuf@ to an output stream.
-- 
-- Supported file formats are currently \"jpeg\", \"tiff\", \"png\", \"ico\" or
-- \"bmp\".
-- 
-- See t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf'.@/save_to_stream/@() for more details.
-- 
-- /Since: 2.36/
pixbufSaveToStreamv ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a, Gio.OutputStream.IsOutputStream b, Gio.Cancellable.IsCancellable c) =>
    a
    -- ^ /@pixbuf@/: a @GdkPixbuf@
    -> b
    -- ^ /@stream@/: a @GOutputStream@ to save the pixbuf to
    -> T.Text
    -- ^ /@type@/: name of file format
    -> Maybe ([T.Text])
    -- ^ /@optionKeys@/: name of options to set
    -> Maybe ([T.Text])
    -- ^ /@optionValues@/: values for named options
    -> Maybe (c)
    -- ^ /@cancellable@/: optional @GCancellable@ object, @NULL@ to ignore
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
pixbufSaveToStreamv :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsPixbuf a, IsOutputStream b,
 IsCancellable c) =>
a -> b -> Text -> Maybe [Text] -> Maybe [Text] -> Maybe c -> m ()
pixbufSaveToStreamv a
pixbuf b
stream Text
type_ Maybe [Text]
optionKeys Maybe [Text]
optionValues Maybe c
cancellable = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    Ptr OutputStream
stream' <- b -> IO (Ptr OutputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
stream
    CString
type_' <- Text -> IO CString
textToCString Text
type_
    Ptr CString
maybeOptionKeys <- case Maybe [Text]
optionKeys of
        Maybe [Text]
Nothing -> Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
forall a. Ptr a
nullPtr
        Just [Text]
jOptionKeys -> do
            Ptr CString
jOptionKeys' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
jOptionKeys
            Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
jOptionKeys'
    Ptr CString
maybeOptionValues <- case Maybe [Text]
optionValues of
        Maybe [Text]
Nothing -> Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
forall a. Ptr a
nullPtr
        Just [Text]
jOptionValues -> do
            Ptr CString
jOptionValues' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
jOptionValues
            Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
jOptionValues'
    Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
        Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just c
jCancellable -> do
            Ptr Cancellable
jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Pixbuf
-> Ptr OutputStream
-> CString
-> Ptr CString
-> Ptr CString
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO CInt
gdk_pixbuf_save_to_streamv Ptr Pixbuf
pixbuf' Ptr OutputStream
stream' CString
type_' Ptr CString
maybeOptionKeys Ptr CString
maybeOptionValues Ptr Cancellable
maybeCancellable
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
stream
        Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
cancellable c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
type_'
        (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionKeys
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionKeys
        (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionValues
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionValues
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
type_'
        (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionKeys
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionKeys
        (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionValues
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionValues
     )

#if defined(ENABLE_OVERLOADING)
data PixbufSaveToStreamvMethodInfo
instance (signature ~ (b -> T.Text -> Maybe ([T.Text]) -> Maybe ([T.Text]) -> Maybe (c) -> m ()), MonadIO m, IsPixbuf a, Gio.OutputStream.IsOutputStream b, Gio.Cancellable.IsCancellable c) => O.OverloadedMethod PixbufSaveToStreamvMethodInfo a signature where
    overloadedMethod = pixbufSaveToStreamv

instance O.OverloadedMethodInfo PixbufSaveToStreamvMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufSaveToStreamv",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufSaveToStreamv"
        })


#endif

-- method Pixbuf::save_to_streamv_async
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkPixbuf`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "stream"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "OutputStream" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GOutputStream` to which to save the pixbuf"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "name of file format"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "option_keys"
--           , argType = TCArray True (-1) (-1) (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "name of options to set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "option_values"
--           , argType = TCArray True (-1) (-1) (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "values for named options"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "optional `GCancellable` object, `NULL` to ignore"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a `GAsyncReadyCallback` to call when the pixbuf is saved"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 7
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the data to pass to the callback function"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_save_to_streamv_async" gdk_pixbuf_save_to_streamv_async :: 
    Ptr Pixbuf ->                           -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    Ptr Gio.OutputStream.OutputStream ->    -- stream : TInterface (Name {namespace = "Gio", name = "OutputStream"})
    CString ->                              -- type : TBasicType TUTF8
    Ptr CString ->                          -- option_keys : TCArray True (-1) (-1) (TBasicType TUTF8)
    Ptr CString ->                          -- option_values : TCArray True (-1) (-1) (TBasicType TUTF8)
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Saves @pixbuf@ to an output stream asynchronously.
-- 
-- For more details see 'GI.GdkPixbuf.Objects.Pixbuf.pixbufSaveToStreamv', which is the synchronous
-- version of this function.
-- 
-- When the operation is finished, @callback@ will be called in the main thread.
-- 
-- You can then call 'GI.GdkPixbuf.Objects.Pixbuf.pixbufSaveToStreamFinish' to get the result of
-- the operation.
-- 
-- /Since: 2.36/
pixbufSaveToStreamvAsync ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a, Gio.OutputStream.IsOutputStream b, Gio.Cancellable.IsCancellable c) =>
    a
    -- ^ /@pixbuf@/: a @GdkPixbuf@
    -> b
    -- ^ /@stream@/: a @GOutputStream@ to which to save the pixbuf
    -> T.Text
    -- ^ /@type@/: name of file format
    -> Maybe ([T.Text])
    -- ^ /@optionKeys@/: name of options to set
    -> Maybe ([T.Text])
    -- ^ /@optionValues@/: values for named options
    -> Maybe (c)
    -- ^ /@cancellable@/: optional @GCancellable@ object, @NULL@ to ignore
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a @GAsyncReadyCallback@ to call when the pixbuf is saved
    -> m ()
pixbufSaveToStreamvAsync :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsPixbuf a, IsOutputStream b,
 IsCancellable c) =>
a
-> b
-> Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe c
-> Maybe AsyncReadyCallback
-> m ()
pixbufSaveToStreamvAsync a
pixbuf b
stream Text
type_ Maybe [Text]
optionKeys Maybe [Text]
optionValues Maybe c
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    Ptr OutputStream
stream' <- b -> IO (Ptr OutputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
stream
    CString
type_' <- Text -> IO CString
textToCString Text
type_
    Ptr CString
maybeOptionKeys <- case Maybe [Text]
optionKeys of
        Maybe [Text]
Nothing -> Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
forall a. Ptr a
nullPtr
        Just [Text]
jOptionKeys -> do
            Ptr CString
jOptionKeys' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
jOptionKeys
            Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
jOptionKeys'
    Ptr CString
maybeOptionValues <- case Maybe [Text]
optionValues of
        Maybe [Text]
Nothing -> Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
forall a. Ptr a
nullPtr
        Just [Text]
jOptionValues -> do
            Ptr CString
jOptionValues' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
jOptionValues
            Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
jOptionValues'
    Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
        Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just c
jCancellable -> do
            Ptr Cancellable
jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr Pixbuf
-> Ptr OutputStream
-> CString
-> Ptr CString
-> Ptr CString
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
gdk_pixbuf_save_to_streamv_async Ptr Pixbuf
pixbuf' Ptr OutputStream
stream' CString
type_' Ptr CString
maybeOptionKeys Ptr CString
maybeOptionValues Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
stream
    Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
cancellable c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
type_'
    (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionKeys
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionKeys
    (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionValues
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionValues
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PixbufSaveToStreamvAsyncMethodInfo
instance (signature ~ (b -> T.Text -> Maybe ([T.Text]) -> Maybe ([T.Text]) -> Maybe (c) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsPixbuf a, Gio.OutputStream.IsOutputStream b, Gio.Cancellable.IsCancellable c) => O.OverloadedMethod PixbufSaveToStreamvAsyncMethodInfo a signature where
    overloadedMethod = pixbufSaveToStreamvAsync

instance O.OverloadedMethodInfo PixbufSaveToStreamvAsyncMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufSaveToStreamvAsync",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufSaveToStreamvAsync"
        })


#endif

-- method Pixbuf::savev
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkPixbuf`." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "filename"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "name of file to save."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "name of file format."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "option_keys"
--           , argType = TCArray True (-1) (-1) (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "name of options to set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "option_values"
--           , argType = TCArray True (-1) (-1) (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "values for named options"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "gdk_pixbuf_savev" gdk_pixbuf_savev :: 
    Ptr Pixbuf ->                           -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    CString ->                              -- filename : TBasicType TFileName
    CString ->                              -- type : TBasicType TUTF8
    Ptr CString ->                          -- option_keys : TCArray True (-1) (-1) (TBasicType TUTF8)
    Ptr CString ->                          -- option_values : TCArray True (-1) (-1) (TBasicType TUTF8)
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Vector version of @gdk_pixbuf_save()@.
-- 
-- Saves pixbuf to a file in @type@, which is currently \"jpeg\", \"png\", \"tiff\", \"ico\" or \"bmp\".
-- 
-- If /@error@/ is set, @FALSE@ will be returned.
-- 
-- See t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf'.@/save/@() for more details.
pixbufSavev ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@pixbuf@/: a @GdkPixbuf@.
    -> [Char]
    -- ^ /@filename@/: name of file to save.
    -> T.Text
    -- ^ /@type@/: name of file format.
    -> Maybe ([T.Text])
    -- ^ /@optionKeys@/: name of options to set
    -> Maybe ([T.Text])
    -- ^ /@optionValues@/: values for named options
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
pixbufSavev :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> String -> Text -> Maybe [Text] -> Maybe [Text] -> m ()
pixbufSavev a
pixbuf String
filename Text
type_ Maybe [Text]
optionKeys Maybe [Text]
optionValues = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    CString
filename' <- String -> IO CString
stringToCString String
filename
    CString
type_' <- Text -> IO CString
textToCString Text
type_
    Ptr CString
maybeOptionKeys <- case Maybe [Text]
optionKeys of
        Maybe [Text]
Nothing -> Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
forall a. Ptr a
nullPtr
        Just [Text]
jOptionKeys -> do
            Ptr CString
jOptionKeys' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
jOptionKeys
            Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
jOptionKeys'
    Ptr CString
maybeOptionValues <- case Maybe [Text]
optionValues of
        Maybe [Text]
Nothing -> Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
forall a. Ptr a
nullPtr
        Just [Text]
jOptionValues -> do
            Ptr CString
jOptionValues' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
jOptionValues
            Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
jOptionValues'
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Pixbuf
-> CString
-> CString
-> Ptr CString
-> Ptr CString
-> Ptr (Ptr GError)
-> IO CInt
gdk_pixbuf_savev Ptr Pixbuf
pixbuf' CString
filename' CString
type_' Ptr CString
maybeOptionKeys Ptr CString
maybeOptionValues
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
type_'
        (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionKeys
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionKeys
        (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionValues
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionValues
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
type_'
        (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionKeys
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionKeys
        (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionValues
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeOptionValues
     )

#if defined(ENABLE_OVERLOADING)
data PixbufSavevMethodInfo
instance (signature ~ ([Char] -> T.Text -> Maybe ([T.Text]) -> Maybe ([T.Text]) -> m ()), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufSavevMethodInfo a signature where
    overloadedMethod = pixbufSavev

instance O.OverloadedMethodInfo PixbufSavevMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufSavev",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufSavev"
        })


#endif

-- method Pixbuf::scale
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "src"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkPixbuf" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the #GdkPixbuf into which to render the results"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest_x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the left coordinate for region to render"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest_y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the top coordinate for region to render"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest_width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the width of the region to render"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest_height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the height of the region to render"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "offset_x"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the offset in the X direction (currently rounded to an integer)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "offset_y"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the offset in the Y direction (currently rounded to an integer)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "scale_x"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the scale factor in the X direction"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "scale_y"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the scale factor in the Y direction"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interp_type"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "InterpType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the interpolation type for the transformation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_scale" gdk_pixbuf_scale :: 
    Ptr Pixbuf ->                           -- src : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    Ptr Pixbuf ->                           -- dest : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    Int32 ->                                -- dest_x : TBasicType TInt
    Int32 ->                                -- dest_y : TBasicType TInt
    Int32 ->                                -- dest_width : TBasicType TInt
    Int32 ->                                -- dest_height : TBasicType TInt
    CDouble ->                              -- offset_x : TBasicType TDouble
    CDouble ->                              -- offset_y : TBasicType TDouble
    CDouble ->                              -- scale_x : TBasicType TDouble
    CDouble ->                              -- scale_y : TBasicType TDouble
    CUInt ->                                -- interp_type : TInterface (Name {namespace = "GdkPixbuf", name = "InterpType"})
    IO ()

-- | Creates a transformation of the source image /@src@/ by scaling by
-- /@scaleX@/ and /@scaleY@/ then translating by /@offsetX@/ and /@offsetY@/,
-- then renders the rectangle (/@destX@/, /@destY@/, /@destWidth@/,
-- /@destHeight@/) of the resulting image onto the destination image
-- replacing the previous contents.
-- 
-- Try to use 'GI.GdkPixbuf.Objects.Pixbuf.pixbufScaleSimple' first; this function is
-- the industrial-strength power tool you can fall back to, if
-- 'GI.GdkPixbuf.Objects.Pixbuf.pixbufScaleSimple' isn\'t powerful enough.
-- 
-- If the source rectangle overlaps the destination rectangle on the
-- same pixbuf, it will be overwritten during the scaling which
-- results in rendering artifacts.
pixbufScale ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a, IsPixbuf b) =>
    a
    -- ^ /@src@/: a t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf'
    -> b
    -- ^ /@dest@/: the t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf' into which to render the results
    -> Int32
    -- ^ /@destX@/: the left coordinate for region to render
    -> Int32
    -- ^ /@destY@/: the top coordinate for region to render
    -> Int32
    -- ^ /@destWidth@/: the width of the region to render
    -> Int32
    -- ^ /@destHeight@/: the height of the region to render
    -> Double
    -- ^ /@offsetX@/: the offset in the X direction (currently rounded to an integer)
    -> Double
    -- ^ /@offsetY@/: the offset in the Y direction (currently rounded to an integer)
    -> Double
    -- ^ /@scaleX@/: the scale factor in the X direction
    -> Double
    -- ^ /@scaleY@/: the scale factor in the Y direction
    -> GdkPixbuf.Enums.InterpType
    -- ^ /@interpType@/: the interpolation type for the transformation.
    -> m ()
pixbufScale :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPixbuf a, IsPixbuf b) =>
a
-> b
-> Int32
-> Int32
-> Int32
-> Int32
-> Double
-> Double
-> Double
-> Double
-> InterpType
-> m ()
pixbufScale a
src b
dest Int32
destX Int32
destY Int32
destWidth Int32
destHeight Double
offsetX Double
offsetY Double
scaleX Double
scaleY InterpType
interpType = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
src' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
src
    Ptr Pixbuf
dest' <- b -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
dest
    let offsetX' :: CDouble
offsetX' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
offsetX
    let offsetY' :: CDouble
offsetY' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
offsetY
    let scaleX' :: CDouble
scaleX' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
scaleX
    let scaleY' :: CDouble
scaleY' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
scaleY
    let interpType' :: CUInt
interpType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (InterpType -> Int) -> InterpType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InterpType -> Int
forall a. Enum a => a -> Int
fromEnum) InterpType
interpType
    Ptr Pixbuf
-> Ptr Pixbuf
-> Int32
-> Int32
-> Int32
-> Int32
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CUInt
-> IO ()
gdk_pixbuf_scale Ptr Pixbuf
src' Ptr Pixbuf
dest' Int32
destX Int32
destY Int32
destWidth Int32
destHeight CDouble
offsetX' CDouble
offsetY' CDouble
scaleX' CDouble
scaleY' CUInt
interpType'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
src
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
dest
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PixbufScaleMethodInfo
instance (signature ~ (b -> Int32 -> Int32 -> Int32 -> Int32 -> Double -> Double -> Double -> Double -> GdkPixbuf.Enums.InterpType -> m ()), MonadIO m, IsPixbuf a, IsPixbuf b) => O.OverloadedMethod PixbufScaleMethodInfo a signature where
    overloadedMethod = pixbufScale

instance O.OverloadedMethodInfo PixbufScaleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufScale",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufScale"
        })


#endif

-- method Pixbuf::scale_simple
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "src"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkPixbuf" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest_width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the width of destination image"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest_height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the height of destination image"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interp_type"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "InterpType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the interpolation type for the transformation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_scale_simple" gdk_pixbuf_scale_simple :: 
    Ptr Pixbuf ->                           -- src : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    Int32 ->                                -- dest_width : TBasicType TInt
    Int32 ->                                -- dest_height : TBasicType TInt
    CUInt ->                                -- interp_type : TInterface (Name {namespace = "GdkPixbuf", name = "InterpType"})
    IO (Ptr Pixbuf)

-- | Create a new pixbuf containing a copy of @src@ scaled to
-- @dest_width@ x @dest_height@.
-- 
-- This function leaves @src@ unaffected.
-- 
-- The @interp_type@ should be @GDK_INTERP_NEAREST@ if you want maximum
-- speed (but when scaling down @GDK_INTERP_NEAREST@ is usually unusably
-- ugly). The default @interp_type@ should be @GDK_INTERP_BILINEAR@ which
-- offers reasonable quality and speed.
-- 
-- You can scale a sub-portion of @src@ by creating a sub-pixbuf
-- pointing into @src@; see 'GI.GdkPixbuf.Objects.Pixbuf.pixbufNewSubpixbuf'.
-- 
-- If @dest_width@ and @dest_height@ are equal to the width and height of
-- @src@, this function will return an unscaled copy of @src@.
-- 
-- For more complicated scaling\/alpha blending see 'GI.GdkPixbuf.Objects.Pixbuf.pixbufScale'
-- and 'GI.GdkPixbuf.Objects.Pixbuf.pixbufComposite'.
pixbufScaleSimple ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@src@/: a t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf'
    -> Int32
    -- ^ /@destWidth@/: the width of destination image
    -> Int32
    -- ^ /@destHeight@/: the height of destination image
    -> GdkPixbuf.Enums.InterpType
    -- ^ /@interpType@/: the interpolation type for the transformation.
    -> m (Maybe Pixbuf)
    -- ^ __Returns:__ the new pixbuf
pixbufScaleSimple :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> Int32 -> Int32 -> InterpType -> m (Maybe Pixbuf)
pixbufScaleSimple a
src Int32
destWidth Int32
destHeight InterpType
interpType = IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Pixbuf) -> m (Maybe Pixbuf))
-> IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
src' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
src
    let interpType' :: CUInt
interpType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (InterpType -> Int) -> InterpType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InterpType -> Int
forall a. Enum a => a -> Int
fromEnum) InterpType
interpType
    Ptr Pixbuf
result <- Ptr Pixbuf -> Int32 -> Int32 -> CUInt -> IO (Ptr Pixbuf)
gdk_pixbuf_scale_simple Ptr Pixbuf
src' Int32
destWidth Int32
destHeight CUInt
interpType'
    Maybe Pixbuf
maybeResult <- Ptr Pixbuf -> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Pixbuf
result ((Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf))
-> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ \Ptr Pixbuf
result' -> do
        Pixbuf
result'' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
Pixbuf) Ptr Pixbuf
result'
        Pixbuf -> IO Pixbuf
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
src
    Maybe Pixbuf -> IO (Maybe Pixbuf)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
maybeResult

#if defined(ENABLE_OVERLOADING)
data PixbufScaleSimpleMethodInfo
instance (signature ~ (Int32 -> Int32 -> GdkPixbuf.Enums.InterpType -> m (Maybe Pixbuf)), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufScaleSimpleMethodInfo a signature where
    overloadedMethod = pixbufScaleSimple

instance O.OverloadedMethodInfo PixbufScaleSimpleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufScaleSimple",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufScaleSimple"
        })


#endif

-- method Pixbuf::set_option
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkPixbuf`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a nul-terminated string."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a nul-terminated string."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_set_option" gdk_pixbuf_set_option :: 
    Ptr Pixbuf ->                           -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    CString ->                              -- key : TBasicType TUTF8
    CString ->                              -- value : TBasicType TUTF8
    IO CInt

-- | Attaches a key\/value pair as an option to a @GdkPixbuf@.
-- 
-- If @key@ already exists in the list of options attached to the @pixbuf@,
-- the new value is ignored and @FALSE@ is returned.
-- 
-- /Since: 2.2/
pixbufSetOption ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbuf a) =>
    a
    -- ^ /@pixbuf@/: a @GdkPixbuf@
    -> T.Text
    -- ^ /@key@/: a nul-terminated string.
    -> T.Text
    -- ^ /@value@/: a nul-terminated string.
    -> m Bool
    -- ^ __Returns:__ @TRUE@ on success
pixbufSetOption :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
a -> Text -> Text -> m Bool
pixbufSetOption a
pixbuf Text
key Text
value = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    CString
key' <- Text -> IO CString
textToCString Text
key
    CString
value' <- Text -> IO CString
textToCString Text
value
    CInt
result <- Ptr Pixbuf -> CString -> CString -> IO CInt
gdk_pixbuf_set_option Ptr Pixbuf
pixbuf' CString
key' CString
value'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
value'
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data PixbufSetOptionMethodInfo
instance (signature ~ (T.Text -> T.Text -> m Bool), MonadIO m, IsPixbuf a) => O.OverloadedMethod PixbufSetOptionMethodInfo a signature where
    overloadedMethod = pixbufSetOption

instance O.OverloadedMethodInfo PixbufSetOptionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.Pixbuf.pixbufSetOption",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Objects-Pixbuf.html#v:pixbufSetOption"
        })


#endif

-- method Pixbuf::calculate_rowstride
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "colorspace"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Colorspace" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Color space for image"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "has_alpha"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Whether the image should have transparency information"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "bits_per_sample"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Number of bits per color sample"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Width of image in pixels, must be > 0"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Height of image in pixels, must be > 0"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_calculate_rowstride" gdk_pixbuf_calculate_rowstride :: 
    CUInt ->                                -- colorspace : TInterface (Name {namespace = "GdkPixbuf", name = "Colorspace"})
    CInt ->                                 -- has_alpha : TBasicType TBoolean
    Int32 ->                                -- bits_per_sample : TBasicType TInt
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    IO Int32

-- | Calculates the rowstride that an image created with those values would
-- have.
-- 
-- This function is useful for front-ends and backends that want to check
-- image values without needing to create a @GdkPixbuf@.
-- 
-- /Since: 2.36.8/
pixbufCalculateRowstride ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GdkPixbuf.Enums.Colorspace
    -- ^ /@colorspace@/: Color space for image
    -> Bool
    -- ^ /@hasAlpha@/: Whether the image should have transparency information
    -> Int32
    -- ^ /@bitsPerSample@/: Number of bits per color sample
    -> Int32
    -- ^ /@width@/: Width of image in pixels, must be > 0
    -> Int32
    -- ^ /@height@/: Height of image in pixels, must be > 0
    -> m Int32
    -- ^ __Returns:__ the rowstride for the given values, or -1 in case of error.
pixbufCalculateRowstride :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Colorspace -> Bool -> Int32 -> Int32 -> Int32 -> m Int32
pixbufCalculateRowstride Colorspace
colorspace Bool
hasAlpha Int32
bitsPerSample Int32
width Int32
height = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    let colorspace' :: CUInt
colorspace' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Colorspace -> Int) -> Colorspace -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Colorspace -> Int
forall a. Enum a => a -> Int
fromEnum) Colorspace
colorspace
    let hasAlpha' :: CInt
hasAlpha' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
hasAlpha
    Int32
result <- CUInt -> CInt -> Int32 -> Int32 -> Int32 -> IO Int32
gdk_pixbuf_calculate_rowstride CUInt
colorspace' CInt
hasAlpha' Int32
bitsPerSample Int32
width Int32
height
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
#endif

-- method Pixbuf::get_file_info
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "filename"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The name of the file to identify."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Return location for the width of the image"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Return location for the height of the image"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "GdkPixbuf" , name = "PixbufFormat" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_get_file_info" gdk_pixbuf_get_file_info :: 
    CString ->                              -- filename : TBasicType TFileName
    Ptr Int32 ->                            -- width : TBasicType TInt
    Ptr Int32 ->                            -- height : TBasicType TInt
    IO (Ptr GdkPixbuf.PixbufFormat.PixbufFormat)

-- | Parses an image file far enough to determine its format and size.
-- 
-- /Since: 2.4/
pixbufGetFileInfo ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [Char]
    -- ^ /@filename@/: The name of the file to identify.
    -> m ((Maybe GdkPixbuf.PixbufFormat.PixbufFormat, Int32, Int32))
    -- ^ __Returns:__ A @GdkPixbufFormat@ describing
    --   the image format of the file
pixbufGetFileInfo :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> m (Maybe PixbufFormat, Int32, Int32)
pixbufGetFileInfo String
filename = IO (Maybe PixbufFormat, Int32, Int32)
-> m (Maybe PixbufFormat, Int32, Int32)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe PixbufFormat, Int32, Int32)
 -> m (Maybe PixbufFormat, Int32, Int32))
-> IO (Maybe PixbufFormat, Int32, Int32)
-> m (Maybe PixbufFormat, Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    CString
filename' <- String -> IO CString
stringToCString String
filename
    Ptr Int32
width <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
height <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr PixbufFormat
result <- CString -> Ptr Int32 -> Ptr Int32 -> IO (Ptr PixbufFormat)
gdk_pixbuf_get_file_info CString
filename' Ptr Int32
width Ptr Int32
height
    Maybe PixbufFormat
maybeResult <- Ptr PixbufFormat
-> (Ptr PixbufFormat -> IO PixbufFormat) -> IO (Maybe PixbufFormat)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr PixbufFormat
result ((Ptr PixbufFormat -> IO PixbufFormat) -> IO (Maybe PixbufFormat))
-> (Ptr PixbufFormat -> IO PixbufFormat) -> IO (Maybe PixbufFormat)
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufFormat
result' -> do
        PixbufFormat
result'' <- ((ManagedPtr PixbufFormat -> PixbufFormat)
-> Ptr PixbufFormat -> IO PixbufFormat
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr PixbufFormat -> PixbufFormat
GdkPixbuf.PixbufFormat.PixbufFormat) Ptr PixbufFormat
result'
        PixbufFormat -> IO PixbufFormat
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PixbufFormat
result''
    Int32
width' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
width
    Int32
height' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
height
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
width
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
height
    (Maybe PixbufFormat, Int32, Int32)
-> IO (Maybe PixbufFormat, Int32, Int32)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe PixbufFormat
maybeResult, Int32
width', Int32
height')

#if defined(ENABLE_OVERLOADING)
#endif

-- method Pixbuf::get_file_info_async
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "filename"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The name of the file to identify"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "optional `GCancellable` object, `NULL` to ignore"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a `GAsyncReadyCallback` to call when the file info is available"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 3
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the data to pass to the callback function"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_get_file_info_async" gdk_pixbuf_get_file_info_async :: 
    CString ->                              -- filename : TBasicType TFileName
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Asynchronously parses an image file far enough to determine its
-- format and size.
-- 
-- For more details see 'GI.GdkPixbuf.Objects.Pixbuf.pixbufGetFileInfo', which is the synchronous
-- version of this function.
-- 
-- When the operation is finished, /@callback@/ will be called in the
-- main thread. You can then call 'GI.GdkPixbuf.Objects.Pixbuf.pixbufGetFileInfoFinish' to
-- get the result of the operation.
-- 
-- /Since: 2.32/
pixbufGetFileInfoAsync ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.Cancellable.IsCancellable a) =>
    [Char]
    -- ^ /@filename@/: The name of the file to identify
    -> Maybe (a)
    -- ^ /@cancellable@/: optional @GCancellable@ object, @NULL@ to ignore
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a @GAsyncReadyCallback@ to call when the file info is available
    -> m ()
pixbufGetFileInfoAsync :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCancellable a) =>
String -> Maybe a -> Maybe AsyncReadyCallback -> m ()
pixbufGetFileInfoAsync String
filename Maybe a
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    CString
filename' <- String -> IO CString
stringToCString String
filename
    Ptr Cancellable
maybeCancellable <- case Maybe a
cancellable of
        Maybe a
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just a
jCancellable -> do
            Ptr Cancellable
jCancellable' <- a -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    CString
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
gdk_pixbuf_get_file_info_async CString
filename' Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
cancellable a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method Pixbuf::get_file_info_finish
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "async_result"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GAsyncResult`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Return location for the width of the image, or `NULL`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Return location for the height of the image, or `NULL`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "GdkPixbuf" , name = "PixbufFormat" })
-- throws : True
-- Skip return : False

foreign import ccall "gdk_pixbuf_get_file_info_finish" gdk_pixbuf_get_file_info_finish :: 
    Ptr Gio.AsyncResult.AsyncResult ->      -- async_result : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr Int32 ->                            -- width : TBasicType TInt
    Ptr Int32 ->                            -- height : TBasicType TInt
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr GdkPixbuf.PixbufFormat.PixbufFormat)

-- | Finishes an asynchronous pixbuf parsing operation started with
-- 'GI.GdkPixbuf.Objects.Pixbuf.pixbufGetFileInfoAsync'.
-- 
-- /Since: 2.32/
pixbufGetFileInfoFinish ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.AsyncResult.IsAsyncResult a) =>
    a
    -- ^ /@asyncResult@/: a @GAsyncResult@
    -> m ((Maybe GdkPixbuf.PixbufFormat.PixbufFormat, Int32, Int32))
    -- ^ __Returns:__ A @GdkPixbufFormat@ describing the
    --   image format of the file /(Can throw 'Data.GI.Base.GError.GError')/
pixbufGetFileInfoFinish :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAsyncResult a) =>
a -> m (Maybe PixbufFormat, Int32, Int32)
pixbufGetFileInfoFinish a
asyncResult = IO (Maybe PixbufFormat, Int32, Int32)
-> m (Maybe PixbufFormat, Int32, Int32)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe PixbufFormat, Int32, Int32)
 -> m (Maybe PixbufFormat, Int32, Int32))
-> IO (Maybe PixbufFormat, Int32, Int32)
-> m (Maybe PixbufFormat, Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr AsyncResult
asyncResult' <- a -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
asyncResult
    Ptr Int32
width <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
height <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    IO (Maybe PixbufFormat, Int32, Int32)
-> IO () -> IO (Maybe PixbufFormat, Int32, Int32)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr PixbufFormat
result <- (Ptr (Ptr GError) -> IO (Ptr PixbufFormat))
-> IO (Ptr PixbufFormat)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr PixbufFormat))
 -> IO (Ptr PixbufFormat))
-> (Ptr (Ptr GError) -> IO (Ptr PixbufFormat))
-> IO (Ptr PixbufFormat)
forall a b. (a -> b) -> a -> b
$ Ptr AsyncResult
-> Ptr Int32
-> Ptr Int32
-> Ptr (Ptr GError)
-> IO (Ptr PixbufFormat)
gdk_pixbuf_get_file_info_finish Ptr AsyncResult
asyncResult' Ptr Int32
width Ptr Int32
height
        Maybe PixbufFormat
maybeResult <- Ptr PixbufFormat
-> (Ptr PixbufFormat -> IO PixbufFormat) -> IO (Maybe PixbufFormat)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr PixbufFormat
result ((Ptr PixbufFormat -> IO PixbufFormat) -> IO (Maybe PixbufFormat))
-> (Ptr PixbufFormat -> IO PixbufFormat) -> IO (Maybe PixbufFormat)
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufFormat
result' -> do
            PixbufFormat
result'' <- ((ManagedPtr PixbufFormat -> PixbufFormat)
-> Ptr PixbufFormat -> IO PixbufFormat
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr PixbufFormat -> PixbufFormat
GdkPixbuf.PixbufFormat.PixbufFormat) Ptr PixbufFormat
result'
            PixbufFormat -> IO PixbufFormat
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PixbufFormat
result''
        Int32
width' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
width
        Int32
height' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
height
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
asyncResult
        Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
width
        Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
height
        (Maybe PixbufFormat, Int32, Int32)
-> IO (Maybe PixbufFormat, Int32, Int32)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe PixbufFormat
maybeResult, Int32
width', Int32
height')
     ) (do
        Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
width
        Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
height
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method Pixbuf::get_formats
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TGSList
--                  (TInterface
--                     Name { namespace = "GdkPixbuf" , name = "PixbufFormat" }))
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_get_formats" gdk_pixbuf_get_formats :: 
    IO (Ptr (GSList (Ptr GdkPixbuf.PixbufFormat.PixbufFormat)))

-- | Obtains the available information about the image formats supported
-- by GdkPixbuf.
-- 
-- /Since: 2.2/
pixbufGetFormats ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m [GdkPixbuf.PixbufFormat.PixbufFormat]
    -- ^ __Returns:__ A list of
    --   support image formats.
pixbufGetFormats :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m [PixbufFormat]
pixbufGetFormats  = IO [PixbufFormat] -> m [PixbufFormat]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [PixbufFormat] -> m [PixbufFormat])
-> IO [PixbufFormat] -> m [PixbufFormat]
forall a b. (a -> b) -> a -> b
$ do
    Ptr (GSList (Ptr PixbufFormat))
result <- IO (Ptr (GSList (Ptr PixbufFormat)))
gdk_pixbuf_get_formats
    [Ptr PixbufFormat]
result' <- Ptr (GSList (Ptr PixbufFormat)) -> IO [Ptr PixbufFormat]
forall a. Ptr (GSList (Ptr a)) -> IO [Ptr a]
unpackGSList Ptr (GSList (Ptr PixbufFormat))
result
    [PixbufFormat]
result'' <- (Ptr PixbufFormat -> IO PixbufFormat)
-> [Ptr PixbufFormat] -> IO [PixbufFormat]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ManagedPtr PixbufFormat -> PixbufFormat)
-> Ptr PixbufFormat -> IO PixbufFormat
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr PixbufFormat -> PixbufFormat
GdkPixbuf.PixbufFormat.PixbufFormat) [Ptr PixbufFormat]
result'
    Ptr (GSList (Ptr PixbufFormat)) -> IO ()
forall a. Ptr (GSList a) -> IO ()
g_slist_free Ptr (GSList (Ptr PixbufFormat))
result
    [PixbufFormat] -> IO [PixbufFormat]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [PixbufFormat]
result''

#if defined(ENABLE_OVERLOADING)
#endif

-- method Pixbuf::init_modules
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Path to directory where the `loaders.cache` is installed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "gdk_pixbuf_init_modules" gdk_pixbuf_init_modules :: 
    CString ->                              -- path : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Initalizes the gdk-pixbuf loader modules referenced by the @loaders.cache@
-- file present inside that directory.
-- 
-- This is to be used by applications that want to ship certain loaders
-- in a different location from the system ones.
-- 
-- This is needed when the OS or runtime ships a minimal number of loaders
-- so as to reduce the potential attack surface of carefully crafted image
-- files, especially for uncommon file types. Applications that require
-- broader image file types coverage, such as image viewers, would be
-- expected to ship the gdk-pixbuf modules in a separate location, bundled
-- with the application in a separate directory from the OS or runtime-
-- provided modules.
-- 
-- /Since: 2.40/
pixbufInitModules ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@path@/: Path to directory where the @loaders.cache@ is installed
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
pixbufInitModules :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Text -> m ()
pixbufInitModules Text
path = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    CString
path' <- Text -> IO CString
textToCString Text
path
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ CString -> Ptr (Ptr GError) -> IO CInt
gdk_pixbuf_init_modules CString
path'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method Pixbuf::new_from_stream_async
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "stream"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "InputStream" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a `GInputStream` from which to load the pixbuf"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "optional `GCancellable` object, `NULL` to ignore"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a `GAsyncReadyCallback` to call when the pixbuf is loaded"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 3
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the data to pass to the callback function"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_new_from_stream_async" gdk_pixbuf_new_from_stream_async :: 
    Ptr Gio.InputStream.InputStream ->      -- stream : TInterface (Name {namespace = "Gio", name = "InputStream"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Creates a new pixbuf by asynchronously loading an image from an input stream.
-- 
-- For more details see 'GI.GdkPixbuf.Objects.Pixbuf.pixbufNewFromStream', which is the synchronous
-- version of this function.
-- 
-- When the operation is finished, /@callback@/ will be called in the main thread.
-- You can then call 'GI.GdkPixbuf.Objects.Pixbuf.pixbufNewFromStreamFinish' to get the result of
-- the operation.
-- 
-- /Since: 2.24/
pixbufNewFromStreamAsync ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.InputStream.IsInputStream a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@stream@/: a @GInputStream@ from which to load the pixbuf
    -> Maybe (b)
    -- ^ /@cancellable@/: optional @GCancellable@ object, @NULL@ to ignore
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a @GAsyncReadyCallback@ to call when the pixbuf is loaded
    -> m ()
pixbufNewFromStreamAsync :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsInputStream a, IsCancellable b) =>
a -> Maybe b -> Maybe AsyncReadyCallback -> m ()
pixbufNewFromStreamAsync a
stream Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr InputStream
stream' <- a -> IO (Ptr InputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr InputStream
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
gdk_pixbuf_new_from_stream_async Ptr InputStream
stream' Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method Pixbuf::new_from_stream_at_scale_async
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "stream"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "InputStream" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a `GInputStream` from which to load the pixbuf"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the width the image should have or -1 to not constrain the width"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the height the image should have or -1 to not constrain the height"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "preserve_aspect_ratio"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "`TRUE` to preserve the image's aspect ratio"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "optional `GCancellable` object, `NULL` to ignore"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a `GAsyncReadyCallback` to call when the pixbuf is loaded"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 6
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the data to pass to the callback function"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_new_from_stream_at_scale_async" gdk_pixbuf_new_from_stream_at_scale_async :: 
    Ptr Gio.InputStream.InputStream ->      -- stream : TInterface (Name {namespace = "Gio", name = "InputStream"})
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    CInt ->                                 -- preserve_aspect_ratio : TBasicType TBoolean
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Creates a new pixbuf by asynchronously loading an image from an input stream.
-- 
-- For more details see 'GI.GdkPixbuf.Objects.Pixbuf.pixbufNewFromStreamAtScale', which is the synchronous
-- version of this function.
-- 
-- When the operation is finished, /@callback@/ will be called in the main thread.
-- You can then call 'GI.GdkPixbuf.Objects.Pixbuf.pixbufNewFromStreamFinish' to get the result of the operation.
-- 
-- /Since: 2.24/
pixbufNewFromStreamAtScaleAsync ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.InputStream.IsInputStream a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@stream@/: a @GInputStream@ from which to load the pixbuf
    -> Int32
    -- ^ /@width@/: the width the image should have or -1 to not constrain the width
    -> Int32
    -- ^ /@height@/: the height the image should have or -1 to not constrain the height
    -> Bool
    -- ^ /@preserveAspectRatio@/: @TRUE@ to preserve the image\'s aspect ratio
    -> Maybe (b)
    -- ^ /@cancellable@/: optional @GCancellable@ object, @NULL@ to ignore
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a @GAsyncReadyCallback@ to call when the pixbuf is loaded
    -> m ()
pixbufNewFromStreamAtScaleAsync :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsInputStream a, IsCancellable b) =>
a
-> Int32
-> Int32
-> Bool
-> Maybe b
-> Maybe AsyncReadyCallback
-> m ()
pixbufNewFromStreamAtScaleAsync a
stream Int32
width Int32
height Bool
preserveAspectRatio Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr InputStream
stream' <- a -> IO (Ptr InputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
    let preserveAspectRatio' :: CInt
preserveAspectRatio' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
preserveAspectRatio
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr InputStream
-> Int32
-> Int32
-> CInt
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
gdk_pixbuf_new_from_stream_at_scale_async Ptr InputStream
stream' Int32
width Int32
height CInt
preserveAspectRatio' Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method Pixbuf::save_to_stream_finish
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "async_result"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GAsyncResult`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "gdk_pixbuf_save_to_stream_finish" gdk_pixbuf_save_to_stream_finish :: 
    Ptr Gio.AsyncResult.AsyncResult ->      -- async_result : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Finishes an asynchronous pixbuf save operation started with
-- @/gdk_pixbuf_save_to_stream_async()/@.
-- 
-- /Since: 2.24/
pixbufSaveToStreamFinish ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.AsyncResult.IsAsyncResult a) =>
    a
    -- ^ /@asyncResult@/: a @GAsyncResult@
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
pixbufSaveToStreamFinish :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAsyncResult a) =>
a -> m ()
pixbufSaveToStreamFinish a
asyncResult = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr AsyncResult
asyncResult' <- a -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
asyncResult
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr AsyncResult -> Ptr (Ptr GError) -> IO CInt
gdk_pixbuf_save_to_stream_finish Ptr AsyncResult
asyncResult'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
asyncResult
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif