{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Incremental image loader.
-- 
-- @GdkPixbufLoader@ provides a way for applications to drive the
-- process of loading an image, by letting them send the image data
-- directly to the loader instead of having the loader read the data
-- from a file. Applications can use this functionality instead of
-- @gdk_pixbuf_new_from_file()@ or @gdk_pixbuf_animation_new_from_file()@
-- when they need to parse image data in small chunks. For example,
-- it should be used when reading an image from a (potentially) slow
-- network connection, or when loading an extremely large file.
-- 
-- To use @GdkPixbufLoader@ to load an image, create a new instance,
-- and call 'GI.GdkPixbuf.Objects.PixbufLoader.pixbufLoaderWrite' to send the data
-- to it. When done, 'GI.GdkPixbuf.Objects.PixbufLoader.pixbufLoaderClose' should be
-- called to end the stream and finalize everything.
-- 
-- The loader will emit three important signals throughout the process:
-- 
--  - [PixbufLoader::sizePrepared]("GI.GdkPixbuf.Objects.PixbufLoader#g:signal:sizePrepared") will be emitted as
--    soon as the image has enough information to determine the size of
--    the image to be used. If you want to scale the image while loading
--    it, you can call 'GI.GdkPixbuf.Objects.PixbufLoader.pixbufLoaderSetSize' in
--    response to this signal.
--  - [PixbufLoader::areaPrepared]("GI.GdkPixbuf.Objects.PixbufLoader#g:signal:areaPrepared") will be emitted as
--    soon as the pixbuf of the desired has been allocated. You can obtain
--    the @GdkPixbuf@ instance by calling 'GI.GdkPixbuf.Objects.PixbufLoader.pixbufLoaderGetPixbuf'.
--    If you want to use it, simply acquire a reference to it. You can
--    also call @gdk_pixbuf_loader_get_pixbuf()@ later to get the same
--    pixbuf.
--  - [PixbufLoader::areaUpdated]("GI.GdkPixbuf.Objects.PixbufLoader#g:signal:areaUpdated") will be emitted every
--    time a region is updated. This way you can update a partially
--    completed image. Note that you do not know anything about the
--    completeness of an image from the updated area. For example, in an
--    interlaced image you will need to make several passes before the
--    image is done loading.
-- 
-- == Loading an animation
-- 
-- Loading an animation is almost as easy as loading an image. Once the
-- first [PixbufLoader::areaPrepared]("GI.GdkPixbuf.Objects.PixbufLoader#g:signal:areaPrepared") signal has been
-- emitted, you can call 'GI.GdkPixbuf.Objects.PixbufLoader.pixbufLoaderGetAnimation' to
-- get the t'GI.GdkPixbuf.Objects.PixbufAnimation.PixbufAnimation' instance, and then call
-- and 'GI.GdkPixbuf.Objects.PixbufAnimation.pixbufAnimationGetIter' to get a
-- t'GI.GdkPixbuf.Objects.PixbufAnimationIter.PixbufAnimationIter' to retrieve the pixbuf for the
-- desired time stamp.

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

module GI.GdkPixbuf.Objects.PixbufLoader
    ( 

-- * Exported types
    PixbufLoader(..)                        ,
    IsPixbufLoader                          ,
    toPixbufLoader                          ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [close]("GI.GdkPixbuf.Objects.PixbufLoader#g:method:close"), [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"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure"), [write]("GI.GdkPixbuf.Objects.PixbufLoader#g:method:write"), [writeBytes]("GI.GdkPixbuf.Objects.PixbufLoader#g:method:writeBytes").
-- 
-- ==== Getters
-- [getAnimation]("GI.GdkPixbuf.Objects.PixbufLoader#g:method:getAnimation"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getFormat]("GI.GdkPixbuf.Objects.PixbufLoader#g:method:getFormat"), [getPixbuf]("GI.GdkPixbuf.Objects.PixbufLoader#g:method:getPixbuf"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setSize]("GI.GdkPixbuf.Objects.PixbufLoader#g:method:setSize").

#if defined(ENABLE_OVERLOADING)
    ResolvePixbufLoaderMethod               ,
#endif

-- ** close #method:close#

#if defined(ENABLE_OVERLOADING)
    PixbufLoaderCloseMethodInfo             ,
#endif
    pixbufLoaderClose                       ,


-- ** getAnimation #method:getAnimation#

#if defined(ENABLE_OVERLOADING)
    PixbufLoaderGetAnimationMethodInfo      ,
#endif
    pixbufLoaderGetAnimation                ,


-- ** getFormat #method:getFormat#

#if defined(ENABLE_OVERLOADING)
    PixbufLoaderGetFormatMethodInfo         ,
#endif
    pixbufLoaderGetFormat                   ,


-- ** getPixbuf #method:getPixbuf#

#if defined(ENABLE_OVERLOADING)
    PixbufLoaderGetPixbufMethodInfo         ,
#endif
    pixbufLoaderGetPixbuf                   ,


-- ** new #method:new#

    pixbufLoaderNew                         ,


-- ** newWithMimeType #method:newWithMimeType#

    pixbufLoaderNewWithMimeType             ,


-- ** newWithType #method:newWithType#

    pixbufLoaderNewWithType                 ,


-- ** setSize #method:setSize#

#if defined(ENABLE_OVERLOADING)
    PixbufLoaderSetSizeMethodInfo           ,
#endif
    pixbufLoaderSetSize                     ,


-- ** write #method:write#

#if defined(ENABLE_OVERLOADING)
    PixbufLoaderWriteMethodInfo             ,
#endif
    pixbufLoaderWrite                       ,


-- ** writeBytes #method:writeBytes#

#if defined(ENABLE_OVERLOADING)
    PixbufLoaderWriteBytesMethodInfo        ,
#endif
    pixbufLoaderWriteBytes                  ,




 -- * Signals


-- ** areaPrepared #signal:areaPrepared#

    PixbufLoaderAreaPreparedCallback        ,
#if defined(ENABLE_OVERLOADING)
    PixbufLoaderAreaPreparedSignalInfo      ,
#endif
    afterPixbufLoaderAreaPrepared           ,
    onPixbufLoaderAreaPrepared              ,


-- ** areaUpdated #signal:areaUpdated#

    PixbufLoaderAreaUpdatedCallback         ,
#if defined(ENABLE_OVERLOADING)
    PixbufLoaderAreaUpdatedSignalInfo       ,
#endif
    afterPixbufLoaderAreaUpdated            ,
    onPixbufLoaderAreaUpdated               ,


-- ** closed #signal:closed#

    PixbufLoaderClosedCallback              ,
#if defined(ENABLE_OVERLOADING)
    PixbufLoaderClosedSignalInfo            ,
#endif
    afterPixbufLoaderClosed                 ,
    onPixbufLoaderClosed                    ,


-- ** sizePrepared #signal:sizePrepared#

    PixbufLoaderSizePreparedCallback        ,
#if defined(ENABLE_OVERLOADING)
    PixbufLoaderSizePreparedSignalInfo      ,
#endif
    afterPixbufLoaderSizePrepared           ,
    onPixbufLoaderSizePrepared              ,




    ) 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.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 {-# SOURCE #-} qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
import {-# SOURCE #-} qualified GI.GdkPixbuf.Objects.PixbufAnimation as GdkPixbuf.PixbufAnimation
import {-# SOURCE #-} qualified GI.GdkPixbuf.Structs.PixbufFormat as GdkPixbuf.PixbufFormat

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

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

foreign import ccall "gdk_pixbuf_loader_get_type"
    c_gdk_pixbuf_loader_get_type :: IO B.Types.GType

instance B.Types.TypedObject PixbufLoader where
    glibType :: IO GType
glibType = IO GType
c_gdk_pixbuf_loader_get_type

instance B.Types.GObject PixbufLoader

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

instance O.HasParentTypes PixbufLoader
type instance O.ParentTypes PixbufLoader = '[GObject.Object.Object]

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

-- | Convert 'PixbufLoader' 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 PixbufLoader) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gdk_pixbuf_loader_get_type
    gvalueSet_ :: Ptr GValue -> Maybe PixbufLoader -> IO ()
gvalueSet_ Ptr GValue
gv Maybe PixbufLoader
P.Nothing = Ptr GValue -> Ptr PixbufLoader -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr PixbufLoader
forall a. Ptr a
FP.nullPtr :: FP.Ptr PixbufLoader)
    gvalueSet_ Ptr GValue
gv (P.Just PixbufLoader
obj) = PixbufLoader -> (Ptr PixbufLoader -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr PixbufLoader
obj (Ptr GValue -> Ptr PixbufLoader -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe PixbufLoader)
gvalueGet_ Ptr GValue
gv = do
        Ptr PixbufLoader
ptr <- Ptr GValue -> IO (Ptr PixbufLoader)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr PixbufLoader)
        if Ptr PixbufLoader
ptr Ptr PixbufLoader -> Ptr PixbufLoader -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr PixbufLoader
forall a. Ptr a
FP.nullPtr
        then PixbufLoader -> Maybe PixbufLoader
forall a. a -> Maybe a
P.Just (PixbufLoader -> Maybe PixbufLoader)
-> IO PixbufLoader -> IO (Maybe PixbufLoader)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr PixbufLoader -> PixbufLoader)
-> Ptr PixbufLoader -> IO PixbufLoader
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr PixbufLoader -> PixbufLoader
PixbufLoader Ptr PixbufLoader
ptr
        else Maybe PixbufLoader -> IO (Maybe PixbufLoader)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PixbufLoader
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolvePixbufLoaderMethod (t :: Symbol) (o :: *) :: * where
    ResolvePixbufLoaderMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolvePixbufLoaderMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolvePixbufLoaderMethod "close" o = PixbufLoaderCloseMethodInfo
    ResolvePixbufLoaderMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolvePixbufLoaderMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolvePixbufLoaderMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolvePixbufLoaderMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolvePixbufLoaderMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolvePixbufLoaderMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolvePixbufLoaderMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolvePixbufLoaderMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolvePixbufLoaderMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolvePixbufLoaderMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolvePixbufLoaderMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolvePixbufLoaderMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolvePixbufLoaderMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolvePixbufLoaderMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolvePixbufLoaderMethod "write" o = PixbufLoaderWriteMethodInfo
    ResolvePixbufLoaderMethod "writeBytes" o = PixbufLoaderWriteBytesMethodInfo
    ResolvePixbufLoaderMethod "getAnimation" o = PixbufLoaderGetAnimationMethodInfo
    ResolvePixbufLoaderMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolvePixbufLoaderMethod "getFormat" o = PixbufLoaderGetFormatMethodInfo
    ResolvePixbufLoaderMethod "getPixbuf" o = PixbufLoaderGetPixbufMethodInfo
    ResolvePixbufLoaderMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolvePixbufLoaderMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolvePixbufLoaderMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolvePixbufLoaderMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolvePixbufLoaderMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolvePixbufLoaderMethod "setSize" o = PixbufLoaderSetSizeMethodInfo
    ResolvePixbufLoaderMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolvePixbufLoaderMethod t PixbufLoader, O.OverloadedMethod info PixbufLoader p) => OL.IsLabel t (PixbufLoader -> 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 ~ ResolvePixbufLoaderMethod t PixbufLoader, O.OverloadedMethod info PixbufLoader p, R.HasField t PixbufLoader p) => R.HasField t PixbufLoader p where
    getField = O.overloadedMethod @info

#endif

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

#endif

-- signal PixbufLoader::area-prepared
-- | This signal is emitted when the pixbuf loader has allocated the
-- pixbuf in the desired size.
-- 
-- After this signal is emitted, applications can call
-- 'GI.GdkPixbuf.Objects.PixbufLoader.pixbufLoaderGetPixbuf' to fetch the partially-loaded
-- pixbuf.
type PixbufLoaderAreaPreparedCallback =
    IO ()

type C_PixbufLoaderAreaPreparedCallback =
    Ptr PixbufLoader ->                     -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_PixbufLoaderAreaPreparedCallback`.
foreign import ccall "wrapper"
    mk_PixbufLoaderAreaPreparedCallback :: C_PixbufLoaderAreaPreparedCallback -> IO (FunPtr C_PixbufLoaderAreaPreparedCallback)

wrap_PixbufLoaderAreaPreparedCallback :: 
    GObject a => (a -> PixbufLoaderAreaPreparedCallback) ->
    C_PixbufLoaderAreaPreparedCallback
wrap_PixbufLoaderAreaPreparedCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_PixbufLoaderAreaPreparedCallback
wrap_PixbufLoaderAreaPreparedCallback a -> IO ()
gi'cb Ptr PixbufLoader
gi'selfPtr Ptr ()
_ = do
    Ptr PixbufLoader -> (PixbufLoader -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr PixbufLoader
gi'selfPtr ((PixbufLoader -> IO ()) -> IO ())
-> (PixbufLoader -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \PixbufLoader
gi'self -> a -> IO ()
gi'cb (PixbufLoader -> a
Coerce.coerce PixbufLoader
gi'self) 


-- | Connect a signal handler for the [areaPrepared](#signal:areaPrepared) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' pixbufLoader #areaPrepared callback
-- @
-- 
-- 
onPixbufLoaderAreaPrepared :: (IsPixbufLoader a, MonadIO m) => a -> ((?self :: a) => PixbufLoaderAreaPreparedCallback) -> m SignalHandlerId
onPixbufLoaderAreaPrepared :: forall a (m :: * -> *).
(IsPixbufLoader a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onPixbufLoaderAreaPrepared a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_PixbufLoaderAreaPreparedCallback
wrapped' = (a -> IO ()) -> C_PixbufLoaderAreaPreparedCallback
forall a.
GObject a =>
(a -> IO ()) -> C_PixbufLoaderAreaPreparedCallback
wrap_PixbufLoaderAreaPreparedCallback a -> IO ()
wrapped
    FunPtr C_PixbufLoaderAreaPreparedCallback
wrapped'' <- C_PixbufLoaderAreaPreparedCallback
-> IO (FunPtr C_PixbufLoaderAreaPreparedCallback)
mk_PixbufLoaderAreaPreparedCallback C_PixbufLoaderAreaPreparedCallback
wrapped'
    a
-> Text
-> FunPtr C_PixbufLoaderAreaPreparedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"area-prepared" FunPtr C_PixbufLoaderAreaPreparedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [areaPrepared](#signal:areaPrepared) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' pixbufLoader #areaPrepared callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterPixbufLoaderAreaPrepared :: (IsPixbufLoader a, MonadIO m) => a -> ((?self :: a) => PixbufLoaderAreaPreparedCallback) -> m SignalHandlerId
afterPixbufLoaderAreaPrepared :: forall a (m :: * -> *).
(IsPixbufLoader a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterPixbufLoaderAreaPrepared a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_PixbufLoaderAreaPreparedCallback
wrapped' = (a -> IO ()) -> C_PixbufLoaderAreaPreparedCallback
forall a.
GObject a =>
(a -> IO ()) -> C_PixbufLoaderAreaPreparedCallback
wrap_PixbufLoaderAreaPreparedCallback a -> IO ()
wrapped
    FunPtr C_PixbufLoaderAreaPreparedCallback
wrapped'' <- C_PixbufLoaderAreaPreparedCallback
-> IO (FunPtr C_PixbufLoaderAreaPreparedCallback)
mk_PixbufLoaderAreaPreparedCallback C_PixbufLoaderAreaPreparedCallback
wrapped'
    a
-> Text
-> FunPtr C_PixbufLoaderAreaPreparedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"area-prepared" FunPtr C_PixbufLoaderAreaPreparedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data PixbufLoaderAreaPreparedSignalInfo
instance SignalInfo PixbufLoaderAreaPreparedSignalInfo where
    type HaskellCallbackType PixbufLoaderAreaPreparedSignalInfo = PixbufLoaderAreaPreparedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_PixbufLoaderAreaPreparedCallback cb
        cb'' <- mk_PixbufLoaderAreaPreparedCallback cb'
        connectSignalFunPtr obj "area-prepared" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.PixbufLoader::area-prepared"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.28/docs/GI-GdkPixbuf-Objects-PixbufLoader.html#g:signal:areaPrepared"})

#endif

-- signal PixbufLoader::area-updated
-- | This signal is emitted when a significant area of the image being
-- loaded has been updated.
-- 
-- Normally it means that a complete scanline has been read in, but
-- it could be a different area as well.
-- 
-- Applications can use this signal to know when to repaint
-- areas of an image that is being loaded.
type PixbufLoaderAreaUpdatedCallback =
    Int32
    -- ^ /@x@/: X offset of upper-left corner of the updated area.
    -> Int32
    -- ^ /@y@/: Y offset of upper-left corner of the updated area.
    -> Int32
    -- ^ /@width@/: Width of updated area.
    -> Int32
    -- ^ /@height@/: Height of updated area.
    -> IO ()

type C_PixbufLoaderAreaUpdatedCallback =
    Ptr PixbufLoader ->                     -- object
    Int32 ->
    Int32 ->
    Int32 ->
    Int32 ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_PixbufLoaderAreaUpdatedCallback`.
foreign import ccall "wrapper"
    mk_PixbufLoaderAreaUpdatedCallback :: C_PixbufLoaderAreaUpdatedCallback -> IO (FunPtr C_PixbufLoaderAreaUpdatedCallback)

wrap_PixbufLoaderAreaUpdatedCallback :: 
    GObject a => (a -> PixbufLoaderAreaUpdatedCallback) ->
    C_PixbufLoaderAreaUpdatedCallback
wrap_PixbufLoaderAreaUpdatedCallback :: forall a.
GObject a =>
(a -> PixbufLoaderAreaUpdatedCallback)
-> C_PixbufLoaderAreaUpdatedCallback
wrap_PixbufLoaderAreaUpdatedCallback a -> PixbufLoaderAreaUpdatedCallback
gi'cb Ptr PixbufLoader
gi'selfPtr Int32
x Int32
y Int32
width Int32
height Ptr ()
_ = do
    Ptr PixbufLoader -> (PixbufLoader -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr PixbufLoader
gi'selfPtr ((PixbufLoader -> IO ()) -> IO ())
-> (PixbufLoader -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \PixbufLoader
gi'self -> a -> PixbufLoaderAreaUpdatedCallback
gi'cb (PixbufLoader -> a
Coerce.coerce PixbufLoader
gi'self)  Int32
x Int32
y Int32
width Int32
height


-- | Connect a signal handler for the [areaUpdated](#signal:areaUpdated) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' pixbufLoader #areaUpdated callback
-- @
-- 
-- 
onPixbufLoaderAreaUpdated :: (IsPixbufLoader a, MonadIO m) => a -> ((?self :: a) => PixbufLoaderAreaUpdatedCallback) -> m SignalHandlerId
onPixbufLoaderAreaUpdated :: forall a (m :: * -> *).
(IsPixbufLoader a, MonadIO m) =>
a
-> ((?self::a) => PixbufLoaderAreaUpdatedCallback)
-> m SignalHandlerId
onPixbufLoaderAreaUpdated a
obj (?self::a) => PixbufLoaderAreaUpdatedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> PixbufLoaderAreaUpdatedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => PixbufLoaderAreaUpdatedCallback
PixbufLoaderAreaUpdatedCallback
cb
    let wrapped' :: C_PixbufLoaderAreaUpdatedCallback
wrapped' = (a -> PixbufLoaderAreaUpdatedCallback)
-> C_PixbufLoaderAreaUpdatedCallback
forall a.
GObject a =>
(a -> PixbufLoaderAreaUpdatedCallback)
-> C_PixbufLoaderAreaUpdatedCallback
wrap_PixbufLoaderAreaUpdatedCallback a -> PixbufLoaderAreaUpdatedCallback
wrapped
    FunPtr C_PixbufLoaderAreaUpdatedCallback
wrapped'' <- C_PixbufLoaderAreaUpdatedCallback
-> IO (FunPtr C_PixbufLoaderAreaUpdatedCallback)
mk_PixbufLoaderAreaUpdatedCallback C_PixbufLoaderAreaUpdatedCallback
wrapped'
    a
-> Text
-> FunPtr C_PixbufLoaderAreaUpdatedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"area-updated" FunPtr C_PixbufLoaderAreaUpdatedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [areaUpdated](#signal:areaUpdated) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' pixbufLoader #areaUpdated callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterPixbufLoaderAreaUpdated :: (IsPixbufLoader a, MonadIO m) => a -> ((?self :: a) => PixbufLoaderAreaUpdatedCallback) -> m SignalHandlerId
afterPixbufLoaderAreaUpdated :: forall a (m :: * -> *).
(IsPixbufLoader a, MonadIO m) =>
a
-> ((?self::a) => PixbufLoaderAreaUpdatedCallback)
-> m SignalHandlerId
afterPixbufLoaderAreaUpdated a
obj (?self::a) => PixbufLoaderAreaUpdatedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> PixbufLoaderAreaUpdatedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => PixbufLoaderAreaUpdatedCallback
PixbufLoaderAreaUpdatedCallback
cb
    let wrapped' :: C_PixbufLoaderAreaUpdatedCallback
wrapped' = (a -> PixbufLoaderAreaUpdatedCallback)
-> C_PixbufLoaderAreaUpdatedCallback
forall a.
GObject a =>
(a -> PixbufLoaderAreaUpdatedCallback)
-> C_PixbufLoaderAreaUpdatedCallback
wrap_PixbufLoaderAreaUpdatedCallback a -> PixbufLoaderAreaUpdatedCallback
wrapped
    FunPtr C_PixbufLoaderAreaUpdatedCallback
wrapped'' <- C_PixbufLoaderAreaUpdatedCallback
-> IO (FunPtr C_PixbufLoaderAreaUpdatedCallback)
mk_PixbufLoaderAreaUpdatedCallback C_PixbufLoaderAreaUpdatedCallback
wrapped'
    a
-> Text
-> FunPtr C_PixbufLoaderAreaUpdatedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"area-updated" FunPtr C_PixbufLoaderAreaUpdatedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data PixbufLoaderAreaUpdatedSignalInfo
instance SignalInfo PixbufLoaderAreaUpdatedSignalInfo where
    type HaskellCallbackType PixbufLoaderAreaUpdatedSignalInfo = PixbufLoaderAreaUpdatedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_PixbufLoaderAreaUpdatedCallback cb
        cb'' <- mk_PixbufLoaderAreaUpdatedCallback cb'
        connectSignalFunPtr obj "area-updated" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.PixbufLoader::area-updated"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.28/docs/GI-GdkPixbuf-Objects-PixbufLoader.html#g:signal:areaUpdated"})

#endif

-- signal PixbufLoader::closed
-- | This signal is emitted when 'GI.GdkPixbuf.Objects.PixbufLoader.pixbufLoaderClose' is called.
-- 
-- It can be used by different parts of an application to receive
-- notification when an image loader is closed by the code that
-- drives it.
type PixbufLoaderClosedCallback =
    IO ()

type C_PixbufLoaderClosedCallback =
    Ptr PixbufLoader ->                     -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_PixbufLoaderClosedCallback`.
foreign import ccall "wrapper"
    mk_PixbufLoaderClosedCallback :: C_PixbufLoaderClosedCallback -> IO (FunPtr C_PixbufLoaderClosedCallback)

wrap_PixbufLoaderClosedCallback :: 
    GObject a => (a -> PixbufLoaderClosedCallback) ->
    C_PixbufLoaderClosedCallback
wrap_PixbufLoaderClosedCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_PixbufLoaderAreaPreparedCallback
wrap_PixbufLoaderClosedCallback a -> IO ()
gi'cb Ptr PixbufLoader
gi'selfPtr Ptr ()
_ = do
    Ptr PixbufLoader -> (PixbufLoader -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr PixbufLoader
gi'selfPtr ((PixbufLoader -> IO ()) -> IO ())
-> (PixbufLoader -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \PixbufLoader
gi'self -> a -> IO ()
gi'cb (PixbufLoader -> a
Coerce.coerce PixbufLoader
gi'self) 


-- | Connect a signal handler for the [closed](#signal:closed) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' pixbufLoader #closed callback
-- @
-- 
-- 
onPixbufLoaderClosed :: (IsPixbufLoader a, MonadIO m) => a -> ((?self :: a) => PixbufLoaderClosedCallback) -> m SignalHandlerId
onPixbufLoaderClosed :: forall a (m :: * -> *).
(IsPixbufLoader a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onPixbufLoaderClosed a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_PixbufLoaderAreaPreparedCallback
wrapped' = (a -> IO ()) -> C_PixbufLoaderAreaPreparedCallback
forall a.
GObject a =>
(a -> IO ()) -> C_PixbufLoaderAreaPreparedCallback
wrap_PixbufLoaderClosedCallback a -> IO ()
wrapped
    FunPtr C_PixbufLoaderAreaPreparedCallback
wrapped'' <- C_PixbufLoaderAreaPreparedCallback
-> IO (FunPtr C_PixbufLoaderAreaPreparedCallback)
mk_PixbufLoaderClosedCallback C_PixbufLoaderAreaPreparedCallback
wrapped'
    a
-> Text
-> FunPtr C_PixbufLoaderAreaPreparedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"closed" FunPtr C_PixbufLoaderAreaPreparedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [closed](#signal:closed) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' pixbufLoader #closed callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterPixbufLoaderClosed :: (IsPixbufLoader a, MonadIO m) => a -> ((?self :: a) => PixbufLoaderClosedCallback) -> m SignalHandlerId
afterPixbufLoaderClosed :: forall a (m :: * -> *).
(IsPixbufLoader a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterPixbufLoaderClosed a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_PixbufLoaderAreaPreparedCallback
wrapped' = (a -> IO ()) -> C_PixbufLoaderAreaPreparedCallback
forall a.
GObject a =>
(a -> IO ()) -> C_PixbufLoaderAreaPreparedCallback
wrap_PixbufLoaderClosedCallback a -> IO ()
wrapped
    FunPtr C_PixbufLoaderAreaPreparedCallback
wrapped'' <- C_PixbufLoaderAreaPreparedCallback
-> IO (FunPtr C_PixbufLoaderAreaPreparedCallback)
mk_PixbufLoaderClosedCallback C_PixbufLoaderAreaPreparedCallback
wrapped'
    a
-> Text
-> FunPtr C_PixbufLoaderAreaPreparedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"closed" FunPtr C_PixbufLoaderAreaPreparedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data PixbufLoaderClosedSignalInfo
instance SignalInfo PixbufLoaderClosedSignalInfo where
    type HaskellCallbackType PixbufLoaderClosedSignalInfo = PixbufLoaderClosedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_PixbufLoaderClosedCallback cb
        cb'' <- mk_PixbufLoaderClosedCallback cb'
        connectSignalFunPtr obj "closed" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.PixbufLoader::closed"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.28/docs/GI-GdkPixbuf-Objects-PixbufLoader.html#g:signal:closed"})

#endif

-- signal PixbufLoader::size-prepared
-- | This signal is emitted when the pixbuf loader has been fed the
-- initial amount of data that is required to figure out the size
-- of the image that it will create.
-- 
-- Applications can call 'GI.GdkPixbuf.Objects.PixbufLoader.pixbufLoaderSetSize' in response
-- to this signal to set the desired size to which the image
-- should be scaled.
type PixbufLoaderSizePreparedCallback =
    Int32
    -- ^ /@width@/: the original width of the image
    -> Int32
    -- ^ /@height@/: the original height of the image
    -> IO ()

type C_PixbufLoaderSizePreparedCallback =
    Ptr PixbufLoader ->                     -- object
    Int32 ->
    Int32 ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_PixbufLoaderSizePreparedCallback`.
foreign import ccall "wrapper"
    mk_PixbufLoaderSizePreparedCallback :: C_PixbufLoaderSizePreparedCallback -> IO (FunPtr C_PixbufLoaderSizePreparedCallback)

wrap_PixbufLoaderSizePreparedCallback :: 
    GObject a => (a -> PixbufLoaderSizePreparedCallback) ->
    C_PixbufLoaderSizePreparedCallback
wrap_PixbufLoaderSizePreparedCallback :: forall a.
GObject a =>
(a -> PixbufLoaderSizePreparedCallback)
-> C_PixbufLoaderSizePreparedCallback
wrap_PixbufLoaderSizePreparedCallback a -> PixbufLoaderSizePreparedCallback
gi'cb Ptr PixbufLoader
gi'selfPtr Int32
width Int32
height Ptr ()
_ = do
    Ptr PixbufLoader -> (PixbufLoader -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr PixbufLoader
gi'selfPtr ((PixbufLoader -> IO ()) -> IO ())
-> (PixbufLoader -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \PixbufLoader
gi'self -> a -> PixbufLoaderSizePreparedCallback
gi'cb (PixbufLoader -> a
Coerce.coerce PixbufLoader
gi'self)  Int32
width Int32
height


-- | Connect a signal handler for the [sizePrepared](#signal:sizePrepared) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' pixbufLoader #sizePrepared callback
-- @
-- 
-- 
onPixbufLoaderSizePrepared :: (IsPixbufLoader a, MonadIO m) => a -> ((?self :: a) => PixbufLoaderSizePreparedCallback) -> m SignalHandlerId
onPixbufLoaderSizePrepared :: forall a (m :: * -> *).
(IsPixbufLoader a, MonadIO m) =>
a
-> ((?self::a) => PixbufLoaderSizePreparedCallback)
-> m SignalHandlerId
onPixbufLoaderSizePrepared a
obj (?self::a) => PixbufLoaderSizePreparedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> PixbufLoaderSizePreparedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => PixbufLoaderSizePreparedCallback
PixbufLoaderSizePreparedCallback
cb
    let wrapped' :: C_PixbufLoaderSizePreparedCallback
wrapped' = (a -> PixbufLoaderSizePreparedCallback)
-> C_PixbufLoaderSizePreparedCallback
forall a.
GObject a =>
(a -> PixbufLoaderSizePreparedCallback)
-> C_PixbufLoaderSizePreparedCallback
wrap_PixbufLoaderSizePreparedCallback a -> PixbufLoaderSizePreparedCallback
wrapped
    FunPtr C_PixbufLoaderSizePreparedCallback
wrapped'' <- C_PixbufLoaderSizePreparedCallback
-> IO (FunPtr C_PixbufLoaderSizePreparedCallback)
mk_PixbufLoaderSizePreparedCallback C_PixbufLoaderSizePreparedCallback
wrapped'
    a
-> Text
-> FunPtr C_PixbufLoaderSizePreparedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"size-prepared" FunPtr C_PixbufLoaderSizePreparedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [sizePrepared](#signal:sizePrepared) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' pixbufLoader #sizePrepared callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterPixbufLoaderSizePrepared :: (IsPixbufLoader a, MonadIO m) => a -> ((?self :: a) => PixbufLoaderSizePreparedCallback) -> m SignalHandlerId
afterPixbufLoaderSizePrepared :: forall a (m :: * -> *).
(IsPixbufLoader a, MonadIO m) =>
a
-> ((?self::a) => PixbufLoaderSizePreparedCallback)
-> m SignalHandlerId
afterPixbufLoaderSizePrepared a
obj (?self::a) => PixbufLoaderSizePreparedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> PixbufLoaderSizePreparedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => PixbufLoaderSizePreparedCallback
PixbufLoaderSizePreparedCallback
cb
    let wrapped' :: C_PixbufLoaderSizePreparedCallback
wrapped' = (a -> PixbufLoaderSizePreparedCallback)
-> C_PixbufLoaderSizePreparedCallback
forall a.
GObject a =>
(a -> PixbufLoaderSizePreparedCallback)
-> C_PixbufLoaderSizePreparedCallback
wrap_PixbufLoaderSizePreparedCallback a -> PixbufLoaderSizePreparedCallback
wrapped
    FunPtr C_PixbufLoaderSizePreparedCallback
wrapped'' <- C_PixbufLoaderSizePreparedCallback
-> IO (FunPtr C_PixbufLoaderSizePreparedCallback)
mk_PixbufLoaderSizePreparedCallback C_PixbufLoaderSizePreparedCallback
wrapped'
    a
-> Text
-> FunPtr C_PixbufLoaderSizePreparedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"size-prepared" FunPtr C_PixbufLoaderSizePreparedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data PixbufLoaderSizePreparedSignalInfo
instance SignalInfo PixbufLoaderSizePreparedSignalInfo where
    type HaskellCallbackType PixbufLoaderSizePreparedSignalInfo = PixbufLoaderSizePreparedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_PixbufLoaderSizePreparedCallback cb
        cb'' <- mk_PixbufLoaderSizePreparedCallback cb'
        connectSignalFunPtr obj "size-prepared" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.PixbufLoader::size-prepared"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.28/docs/GI-GdkPixbuf-Objects-PixbufLoader.html#g:signal:sizePrepared"})

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList PixbufLoader
type instance O.AttributeList PixbufLoader = PixbufLoaderAttributeList
type PixbufLoaderAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList PixbufLoader = PixbufLoaderSignalList
type PixbufLoaderSignalList = ('[ '("areaPrepared", PixbufLoaderAreaPreparedSignalInfo), '("areaUpdated", PixbufLoaderAreaUpdatedSignalInfo), '("closed", PixbufLoaderClosedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("sizePrepared", PixbufLoaderSizePreparedSignalInfo)] :: [(Symbol, *)])

#endif

-- method PixbufLoader::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "GdkPixbuf" , name = "PixbufLoader" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_loader_new" gdk_pixbuf_loader_new :: 
    IO (Ptr PixbufLoader)

-- | Creates a new pixbuf loader object.
pixbufLoaderNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m PixbufLoader
    -- ^ __Returns:__ A newly-created pixbuf loader.
pixbufLoaderNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m PixbufLoader
pixbufLoaderNew  = IO PixbufLoader -> m PixbufLoader
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PixbufLoader -> m PixbufLoader)
-> IO PixbufLoader -> m PixbufLoader
forall a b. (a -> b) -> a -> b
$ do
    Ptr PixbufLoader
result <- IO (Ptr PixbufLoader)
gdk_pixbuf_loader_new
    Text -> Ptr PixbufLoader -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pixbufLoaderNew" Ptr PixbufLoader
result
    PixbufLoader
result' <- ((ManagedPtr PixbufLoader -> PixbufLoader)
-> Ptr PixbufLoader -> IO PixbufLoader
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr PixbufLoader -> PixbufLoader
PixbufLoader) Ptr PixbufLoader
result
    PixbufLoader -> IO PixbufLoader
forall (m :: * -> *) a. Monad m => a -> m a
return PixbufLoader
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method PixbufLoader::new_with_mime_type
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "mime_type"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the mime type to be loaded"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "GdkPixbuf" , name = "PixbufLoader" })
-- throws : True
-- Skip return : False

foreign import ccall "gdk_pixbuf_loader_new_with_mime_type" gdk_pixbuf_loader_new_with_mime_type :: 
    CString ->                              -- mime_type : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr PixbufLoader)

-- | Creates a new pixbuf loader object that always attempts to parse
-- image data as if it were an image of MIME type /@mimeType@/, instead of
-- identifying the type automatically.
-- 
-- This function is useful if you want an error if the image isn\'t the
-- expected MIME type; for loading image formats that can\'t be reliably
-- identified by looking at the data; or if the user manually forces a
-- specific MIME type.
-- 
-- The list of supported mime types depends on what image loaders
-- are installed, but typically \"image\/png\", \"image\/jpeg\", \"image\/gif\",
-- \"image\/tiff\" and \"image\/x-xpixmap\" are among the supported mime types.
-- To obtain the full list of supported mime types, call
-- 'GI.GdkPixbuf.Structs.PixbufFormat.pixbufFormatGetMimeTypes' on each of the t'GI.GdkPixbuf.Structs.PixbufFormat.PixbufFormat'
-- structs returned by 'GI.GdkPixbuf.Objects.Pixbuf.pixbufGetFormats'.
-- 
-- /Since: 2.4/
pixbufLoaderNewWithMimeType ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@mimeType@/: the mime type to be loaded
    -> m PixbufLoader
    -- ^ __Returns:__ A newly-created pixbuf loader. /(Can throw 'Data.GI.Base.GError.GError')/
pixbufLoaderNewWithMimeType :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m PixbufLoader
pixbufLoaderNewWithMimeType Text
mimeType = IO PixbufLoader -> m PixbufLoader
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PixbufLoader -> m PixbufLoader)
-> IO PixbufLoader -> m PixbufLoader
forall a b. (a -> b) -> a -> b
$ do
    CString
mimeType' <- Text -> IO CString
textToCString Text
mimeType
    IO PixbufLoader -> IO () -> IO PixbufLoader
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr PixbufLoader
result <- (Ptr (Ptr GError) -> IO (Ptr PixbufLoader))
-> IO (Ptr PixbufLoader)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr PixbufLoader))
 -> IO (Ptr PixbufLoader))
-> (Ptr (Ptr GError) -> IO (Ptr PixbufLoader))
-> IO (Ptr PixbufLoader)
forall a b. (a -> b) -> a -> b
$ CString -> Ptr (Ptr GError) -> IO (Ptr PixbufLoader)
gdk_pixbuf_loader_new_with_mime_type CString
mimeType'
        Text -> Ptr PixbufLoader -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pixbufLoaderNewWithMimeType" Ptr PixbufLoader
result
        PixbufLoader
result' <- ((ManagedPtr PixbufLoader -> PixbufLoader)
-> Ptr PixbufLoader -> IO PixbufLoader
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr PixbufLoader -> PixbufLoader
PixbufLoader) Ptr PixbufLoader
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
mimeType'
        PixbufLoader -> IO PixbufLoader
forall (m :: * -> *) a. Monad m => a -> m a
return PixbufLoader
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
mimeType'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method PixbufLoader::new_with_type
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "image_type"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "name of the image format to be loaded with the image"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "GdkPixbuf" , name = "PixbufLoader" })
-- throws : True
-- Skip return : False

foreign import ccall "gdk_pixbuf_loader_new_with_type" gdk_pixbuf_loader_new_with_type :: 
    CString ->                              -- image_type : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr PixbufLoader)

-- | Creates a new pixbuf loader object that always attempts to parse
-- image data as if it were an image of type /@imageType@/, instead of
-- identifying the type automatically.
-- 
-- This function is useful if you want an error if the image isn\'t the
-- expected type; for loading image formats that can\'t be reliably
-- identified by looking at the data; or if the user manually forces
-- a specific type.
-- 
-- The list of supported image formats depends on what image loaders
-- are installed, but typically \"png\", \"jpeg\", \"gif\", \"tiff\" and
-- \"xpm\" are among the supported formats. To obtain the full list of
-- supported image formats, call 'GI.GdkPixbuf.Structs.PixbufFormat.pixbufFormatGetName' on each
-- of the t'GI.GdkPixbuf.Structs.PixbufFormat.PixbufFormat' structs returned by 'GI.GdkPixbuf.Objects.Pixbuf.pixbufGetFormats'.
pixbufLoaderNewWithType ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@imageType@/: name of the image format to be loaded with the image
    -> m PixbufLoader
    -- ^ __Returns:__ A newly-created pixbuf loader. /(Can throw 'Data.GI.Base.GError.GError')/
pixbufLoaderNewWithType :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m PixbufLoader
pixbufLoaderNewWithType Text
imageType = IO PixbufLoader -> m PixbufLoader
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PixbufLoader -> m PixbufLoader)
-> IO PixbufLoader -> m PixbufLoader
forall a b. (a -> b) -> a -> b
$ do
    CString
imageType' <- Text -> IO CString
textToCString Text
imageType
    IO PixbufLoader -> IO () -> IO PixbufLoader
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr PixbufLoader
result <- (Ptr (Ptr GError) -> IO (Ptr PixbufLoader))
-> IO (Ptr PixbufLoader)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr PixbufLoader))
 -> IO (Ptr PixbufLoader))
-> (Ptr (Ptr GError) -> IO (Ptr PixbufLoader))
-> IO (Ptr PixbufLoader)
forall a b. (a -> b) -> a -> b
$ CString -> Ptr (Ptr GError) -> IO (Ptr PixbufLoader)
gdk_pixbuf_loader_new_with_type CString
imageType'
        Text -> Ptr PixbufLoader -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pixbufLoaderNewWithType" Ptr PixbufLoader
result
        PixbufLoader
result' <- ((ManagedPtr PixbufLoader -> PixbufLoader)
-> Ptr PixbufLoader -> IO PixbufLoader
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr PixbufLoader -> PixbufLoader
PixbufLoader) Ptr PixbufLoader
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
imageType'
        PixbufLoader -> IO PixbufLoader
forall (m :: * -> *) a. Monad m => a -> m a
return PixbufLoader
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
imageType'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method PixbufLoader::close
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "loader"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "PixbufLoader" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A pixbuf loader." , 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_loader_close" gdk_pixbuf_loader_close :: 
    Ptr PixbufLoader ->                     -- loader : TInterface (Name {namespace = "GdkPixbuf", name = "PixbufLoader"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Informs a pixbuf loader that no further writes with
-- 'GI.GdkPixbuf.Objects.PixbufLoader.pixbufLoaderWrite' will occur, so that it can free its
-- internal loading structures.
-- 
-- This function also tries to parse any data that hasn\'t yet been parsed;
-- if the remaining data is partial or corrupt, an error will be returned.
-- 
-- If @FALSE@ is returned, @error@ will be set to an error from the
-- @GDK_PIXBUF_ERROR@ or @G_FILE_ERROR@ domains.
-- 
-- If you\'re just cancelling a load rather than expecting it to be finished,
-- passing @NULL@ for @error@ to ignore it is reasonable.
-- 
-- Remember that this function does not release a reference on the loader, so
-- you will need to explicitly release any reference you hold.
pixbufLoaderClose ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbufLoader a) =>
    a
    -- ^ /@loader@/: A pixbuf loader.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
pixbufLoaderClose :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbufLoader a) =>
a -> m ()
pixbufLoaderClose a
loader = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr PixbufLoader
loader' <- a -> IO (Ptr PixbufLoader)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
loader
    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 PixbufLoader -> Ptr (Ptr GError) -> IO CInt
gdk_pixbuf_loader_close Ptr PixbufLoader
loader'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
loader
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data PixbufLoaderCloseMethodInfo
instance (signature ~ (m ()), MonadIO m, IsPixbufLoader a) => O.OverloadedMethod PixbufLoaderCloseMethodInfo a signature where
    overloadedMethod = pixbufLoaderClose

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


#endif

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

foreign import ccall "gdk_pixbuf_loader_get_animation" gdk_pixbuf_loader_get_animation :: 
    Ptr PixbufLoader ->                     -- loader : TInterface (Name {namespace = "GdkPixbuf", name = "PixbufLoader"})
    IO (Ptr GdkPixbuf.PixbufAnimation.PixbufAnimation)

-- | Queries the t'GI.GdkPixbuf.Objects.PixbufAnimation.PixbufAnimation' that a pixbuf loader is currently creating.
-- 
-- In general it only makes sense to call this function after the
-- [PixbufLoader::areaPrepared]("GI.GdkPixbuf.Objects.PixbufLoader#g:signal:areaPrepared") signal has been emitted by
-- the loader.
-- 
-- If the loader doesn\'t have enough bytes yet, and hasn\'t emitted the @area-prepared@
-- signal, this function will return @NULL@.
pixbufLoaderGetAnimation ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbufLoader a) =>
    a
    -- ^ /@loader@/: A pixbuf loader
    -> m (Maybe GdkPixbuf.PixbufAnimation.PixbufAnimation)
    -- ^ __Returns:__ The animation that the loader is
    --   currently loading
pixbufLoaderGetAnimation :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbufLoader a) =>
a -> m (Maybe PixbufAnimation)
pixbufLoaderGetAnimation a
loader = IO (Maybe PixbufAnimation) -> m (Maybe PixbufAnimation)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe PixbufAnimation) -> m (Maybe PixbufAnimation))
-> IO (Maybe PixbufAnimation) -> m (Maybe PixbufAnimation)
forall a b. (a -> b) -> a -> b
$ do
    Ptr PixbufLoader
loader' <- a -> IO (Ptr PixbufLoader)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
loader
    Ptr PixbufAnimation
result <- Ptr PixbufLoader -> IO (Ptr PixbufAnimation)
gdk_pixbuf_loader_get_animation Ptr PixbufLoader
loader'
    Maybe PixbufAnimation
maybeResult <- Ptr PixbufAnimation
-> (Ptr PixbufAnimation -> IO PixbufAnimation)
-> IO (Maybe PixbufAnimation)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr PixbufAnimation
result ((Ptr PixbufAnimation -> IO PixbufAnimation)
 -> IO (Maybe PixbufAnimation))
-> (Ptr PixbufAnimation -> IO PixbufAnimation)
-> IO (Maybe PixbufAnimation)
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufAnimation
result' -> do
        PixbufAnimation
result'' <- ((ManagedPtr PixbufAnimation -> PixbufAnimation)
-> Ptr PixbufAnimation -> IO PixbufAnimation
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr PixbufAnimation -> PixbufAnimation
GdkPixbuf.PixbufAnimation.PixbufAnimation) Ptr PixbufAnimation
result'
        PixbufAnimation -> IO PixbufAnimation
forall (m :: * -> *) a. Monad m => a -> m a
return PixbufAnimation
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
loader
    Maybe PixbufAnimation -> IO (Maybe PixbufAnimation)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PixbufAnimation
maybeResult

#if defined(ENABLE_OVERLOADING)
data PixbufLoaderGetAnimationMethodInfo
instance (signature ~ (m (Maybe GdkPixbuf.PixbufAnimation.PixbufAnimation)), MonadIO m, IsPixbufLoader a) => O.OverloadedMethod PixbufLoaderGetAnimationMethodInfo a signature where
    overloadedMethod = pixbufLoaderGetAnimation

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


#endif

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

foreign import ccall "gdk_pixbuf_loader_get_format" gdk_pixbuf_loader_get_format :: 
    Ptr PixbufLoader ->                     -- loader : TInterface (Name {namespace = "GdkPixbuf", name = "PixbufLoader"})
    IO (Ptr GdkPixbuf.PixbufFormat.PixbufFormat)

-- | Obtains the available information about the format of the
-- currently loading image file.
-- 
-- /Since: 2.2/
pixbufLoaderGetFormat ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbufLoader a) =>
    a
    -- ^ /@loader@/: A pixbuf loader.
    -> m (Maybe GdkPixbuf.PixbufFormat.PixbufFormat)
    -- ^ __Returns:__ A t'GI.GdkPixbuf.Structs.PixbufFormat.PixbufFormat'
pixbufLoaderGetFormat :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbufLoader a) =>
a -> m (Maybe PixbufFormat)
pixbufLoaderGetFormat a
loader = IO (Maybe PixbufFormat) -> m (Maybe PixbufFormat)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe PixbufFormat) -> m (Maybe PixbufFormat))
-> IO (Maybe PixbufFormat) -> m (Maybe PixbufFormat)
forall a b. (a -> b) -> a -> b
$ do
    Ptr PixbufLoader
loader' <- a -> IO (Ptr PixbufLoader)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
loader
    Ptr PixbufFormat
result <- Ptr PixbufLoader -> IO (Ptr PixbufFormat)
gdk_pixbuf_loader_get_format Ptr PixbufLoader
loader'
    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 (m :: * -> *) a. Monad m => a -> m a
return PixbufFormat
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
loader
    Maybe PixbufFormat -> IO (Maybe PixbufFormat)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PixbufFormat
maybeResult

#if defined(ENABLE_OVERLOADING)
data PixbufLoaderGetFormatMethodInfo
instance (signature ~ (m (Maybe GdkPixbuf.PixbufFormat.PixbufFormat)), MonadIO m, IsPixbufLoader a) => O.OverloadedMethod PixbufLoaderGetFormatMethodInfo a signature where
    overloadedMethod = pixbufLoaderGetFormat

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


#endif

-- method PixbufLoader::get_pixbuf
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "loader"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "PixbufLoader" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A pixbuf loader." , 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_loader_get_pixbuf" gdk_pixbuf_loader_get_pixbuf :: 
    Ptr PixbufLoader ->                     -- loader : TInterface (Name {namespace = "GdkPixbuf", name = "PixbufLoader"})
    IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)

-- | Queries the t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf' that a pixbuf loader is currently creating.
-- 
-- In general it only makes sense to call this function after the
-- [PixbufLoader::areaPrepared]("GI.GdkPixbuf.Objects.PixbufLoader#g:signal:areaPrepared") signal has been
-- emitted by the loader; this means that enough data has been read
-- to know the size of the image that will be allocated.
-- 
-- If the loader has not received enough data via 'GI.GdkPixbuf.Objects.PixbufLoader.pixbufLoaderWrite',
-- then this function returns @NULL@.
-- 
-- The returned pixbuf will be the same in all future calls to the loader,
-- so if you want to keep using it, you should acquire a reference to it.
-- 
-- Additionally, if the loader is an animation, it will return the \"static
-- image\" of the animation (see 'GI.GdkPixbuf.Objects.PixbufAnimation.pixbufAnimationGetStaticImage').
pixbufLoaderGetPixbuf ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbufLoader a) =>
    a
    -- ^ /@loader@/: A pixbuf loader.
    -> m (Maybe GdkPixbuf.Pixbuf.Pixbuf)
    -- ^ __Returns:__ The pixbuf that the loader is
    --   creating
pixbufLoaderGetPixbuf :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbufLoader a) =>
a -> m (Maybe Pixbuf)
pixbufLoaderGetPixbuf a
loader = IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
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 PixbufLoader
loader' <- a -> IO (Ptr PixbufLoader)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
loader
    Ptr Pixbuf
result <- Ptr PixbufLoader -> IO (Ptr Pixbuf)
gdk_pixbuf_loader_get_pixbuf Ptr PixbufLoader
loader'
    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
newObject ManagedPtr Pixbuf -> Pixbuf
GdkPixbuf.Pixbuf.Pixbuf) Ptr Pixbuf
result'
        Pixbuf -> IO Pixbuf
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
loader
    Maybe Pixbuf -> IO (Maybe Pixbuf)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
maybeResult

#if defined(ENABLE_OVERLOADING)
data PixbufLoaderGetPixbufMethodInfo
instance (signature ~ (m (Maybe GdkPixbuf.Pixbuf.Pixbuf)), MonadIO m, IsPixbufLoader a) => O.OverloadedMethod PixbufLoaderGetPixbufMethodInfo a signature where
    overloadedMethod = pixbufLoaderGetPixbuf

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


#endif

-- method PixbufLoader::set_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "loader"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "PixbufLoader" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A pixbuf loader." , 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 desired width of the image being loaded."
--                 , 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 desired height of the image being loaded."
--                 , 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_loader_set_size" gdk_pixbuf_loader_set_size :: 
    Ptr PixbufLoader ->                     -- loader : TInterface (Name {namespace = "GdkPixbuf", name = "PixbufLoader"})
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    IO ()

-- | Causes the image to be scaled while it is loaded.
-- 
-- The desired image size can be determined relative to the original
-- size of the image by calling 'GI.GdkPixbuf.Objects.PixbufLoader.pixbufLoaderSetSize' from a
-- signal handler for the [sizePrepared](#g:signal:sizePrepared) signal.
-- 
-- Attempts to set the desired image size  are ignored after the
-- emission of the [sizePrepared](#g:signal:sizePrepared) signal.
-- 
-- /Since: 2.2/
pixbufLoaderSetSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbufLoader a) =>
    a
    -- ^ /@loader@/: A pixbuf loader.
    -> Int32
    -- ^ /@width@/: The desired width of the image being loaded.
    -> Int32
    -- ^ /@height@/: The desired height of the image being loaded.
    -> m ()
pixbufLoaderSetSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbufLoader a) =>
a -> Int32 -> Int32 -> m ()
pixbufLoaderSetSize a
loader Int32
width Int32
height = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr PixbufLoader
loader' <- a -> IO (Ptr PixbufLoader)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
loader
    Ptr PixbufLoader -> PixbufLoaderSizePreparedCallback
gdk_pixbuf_loader_set_size Ptr PixbufLoader
loader' Int32
width Int32
height
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
loader
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PixbufLoaderSetSizeMethodInfo
instance (signature ~ (Int32 -> Int32 -> m ()), MonadIO m, IsPixbufLoader a) => O.OverloadedMethod PixbufLoaderSetSizeMethodInfo a signature where
    overloadedMethod = pixbufLoaderSetSize

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


#endif

-- method PixbufLoader::write
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "loader"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "PixbufLoader" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A pixbuf loader." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "buf"
--           , argType = TCArray False (-1) 2 (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Pointer to image data."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "count"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Length of the @buf buffer in bytes."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "count"
--              , argType = TBasicType TUInt64
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "Length of the @buf buffer in bytes."
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "gdk_pixbuf_loader_write" gdk_pixbuf_loader_write :: 
    Ptr PixbufLoader ->                     -- loader : TInterface (Name {namespace = "GdkPixbuf", name = "PixbufLoader"})
    Ptr Word8 ->                            -- buf : TCArray False (-1) 2 (TBasicType TUInt8)
    Word64 ->                               -- count : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Parses the next @count@ bytes in the given image buffer.
pixbufLoaderWrite ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbufLoader a) =>
    a
    -- ^ /@loader@/: A pixbuf loader.
    -> ByteString
    -- ^ /@buf@/: Pointer to image data.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
pixbufLoaderWrite :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbufLoader a) =>
a -> ByteString -> m ()
pixbufLoaderWrite a
loader ByteString
buf = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    let count :: Word64
count = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
buf
    Ptr PixbufLoader
loader' <- a -> IO (Ptr PixbufLoader)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
loader
    Ptr Word8
buf' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
buf
    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 PixbufLoader
-> Ptr Word8 -> Word64 -> Ptr (Ptr GError) -> IO CInt
gdk_pixbuf_loader_write Ptr PixbufLoader
loader' Ptr Word8
buf' Word64
count
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
loader
        Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
buf'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
buf'
     )

#if defined(ENABLE_OVERLOADING)
data PixbufLoaderWriteMethodInfo
instance (signature ~ (ByteString -> m ()), MonadIO m, IsPixbufLoader a) => O.OverloadedMethod PixbufLoaderWriteMethodInfo a signature where
    overloadedMethod = pixbufLoaderWrite

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


#endif

-- method PixbufLoader::write_bytes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "loader"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "PixbufLoader" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A pixbuf loader." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "buffer"
--           , argType = TInterface Name { namespace = "GLib" , name = "Bytes" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The image data as a `GBytes` buffer."
--                 , 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_loader_write_bytes" gdk_pixbuf_loader_write_bytes :: 
    Ptr PixbufLoader ->                     -- loader : TInterface (Name {namespace = "GdkPixbuf", name = "PixbufLoader"})
    Ptr GLib.Bytes.Bytes ->                 -- buffer : TInterface (Name {namespace = "GLib", name = "Bytes"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Parses the next contents of the given image buffer.
-- 
-- /Since: 2.30/
pixbufLoaderWriteBytes ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbufLoader a) =>
    a
    -- ^ /@loader@/: A pixbuf loader.
    -> GLib.Bytes.Bytes
    -- ^ /@buffer@/: The image data as a @GBytes@ buffer.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
pixbufLoaderWriteBytes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbufLoader a) =>
a -> Bytes -> m ()
pixbufLoaderWriteBytes a
loader Bytes
buffer = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr PixbufLoader
loader' <- a -> IO (Ptr PixbufLoader)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
loader
    Ptr Bytes
buffer' <- Bytes -> IO (Ptr Bytes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bytes
buffer
    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 PixbufLoader -> Ptr Bytes -> Ptr (Ptr GError) -> IO CInt
gdk_pixbuf_loader_write_bytes Ptr PixbufLoader
loader' Ptr Bytes
buffer'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
loader
        Bytes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bytes
buffer
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data PixbufLoaderWriteBytesMethodInfo
instance (signature ~ (GLib.Bytes.Bytes -> m ()), MonadIO m, IsPixbufLoader a) => O.OverloadedMethod PixbufLoaderWriteBytesMethodInfo a signature where
    overloadedMethod = pixbufLoaderWriteBytes

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


#endif