{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GdkPixbuf.Objects.PixbufLoader
(
PixbufLoader(..) ,
IsPixbufLoader ,
toPixbufLoader ,
#if defined(ENABLE_OVERLOADING)
ResolvePixbufLoaderMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
PixbufLoaderCloseMethodInfo ,
#endif
pixbufLoaderClose ,
#if defined(ENABLE_OVERLOADING)
PixbufLoaderGetAnimationMethodInfo ,
#endif
pixbufLoaderGetAnimation ,
#if defined(ENABLE_OVERLOADING)
PixbufLoaderGetFormatMethodInfo ,
#endif
pixbufLoaderGetFormat ,
#if defined(ENABLE_OVERLOADING)
PixbufLoaderGetPixbufMethodInfo ,
#endif
pixbufLoaderGetPixbuf ,
pixbufLoaderNew ,
pixbufLoaderNewWithMimeType ,
pixbufLoaderNewWithType ,
#if defined(ENABLE_OVERLOADING)
PixbufLoaderSetSizeMethodInfo ,
#endif
pixbufLoaderSetSize ,
#if defined(ENABLE_OVERLOADING)
PixbufLoaderWriteMethodInfo ,
#endif
pixbufLoaderWrite ,
#if defined(ENABLE_OVERLOADING)
PixbufLoaderWriteBytesMethodInfo ,
#endif
pixbufLoaderWriteBytes ,
PixbufLoaderAreaPreparedCallback ,
#if defined(ENABLE_OVERLOADING)
PixbufLoaderAreaPreparedSignalInfo ,
#endif
afterPixbufLoaderAreaPrepared ,
onPixbufLoaderAreaPrepared ,
PixbufLoaderAreaUpdatedCallback ,
#if defined(ENABLE_OVERLOADING)
PixbufLoaderAreaUpdatedSignalInfo ,
#endif
afterPixbufLoaderAreaUpdated ,
onPixbufLoaderAreaUpdated ,
PixbufLoaderClosedCallback ,
#if defined(ENABLE_OVERLOADING)
PixbufLoaderClosedSignalInfo ,
#endif
afterPixbufLoaderClosed ,
onPixbufLoaderClosed ,
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.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.Kind as DK
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
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
$c== :: PixbufLoader -> PixbufLoader -> Bool
== :: PixbufLoader -> PixbufLoader -> Bool
$c/= :: PixbufLoader -> PixbufLoader -> Bool
/= :: 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
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]
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 a. IO a -> m a
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
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 a. a -> IO a
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 :: DK.Type) :: DK.Type 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
type PixbufLoaderAreaPreparedCallback =
IO ()
type C_PixbufLoaderAreaPreparedCallback =
Ptr PixbufLoader ->
Ptr () ->
IO ()
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
forall a b. Coercible a b => a -> b
Coerce.coerce PixbufLoader
gi'self)
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 a. IO a -> m a
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
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 a. IO a -> m a
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.31/docs/GI-GdkPixbuf-Objects-PixbufLoader.html#g:signal:areaPrepared"})
#endif
type PixbufLoaderAreaUpdatedCallback =
Int32
-> Int32
-> Int32
-> Int32
-> IO ()
type C_PixbufLoaderAreaUpdatedCallback =
Ptr PixbufLoader ->
Int32 ->
Int32 ->
Int32 ->
Int32 ->
Ptr () ->
IO ()
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
forall a b. Coercible a b => a -> b
Coerce.coerce PixbufLoader
gi'self) Int32
x Int32
y Int32
width Int32
height
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 a. IO a -> m a
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
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 a. IO a -> m a
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.31/docs/GI-GdkPixbuf-Objects-PixbufLoader.html#g:signal:areaUpdated"})
#endif
type PixbufLoaderClosedCallback =
IO ()
type C_PixbufLoaderClosedCallback =
Ptr PixbufLoader ->
Ptr () ->
IO ()
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
forall a b. Coercible a b => a -> b
Coerce.coerce PixbufLoader
gi'self)
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 a. IO a -> m a
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
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 a. IO a -> m a
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.31/docs/GI-GdkPixbuf-Objects-PixbufLoader.html#g:signal:closed"})
#endif
type PixbufLoaderSizePreparedCallback =
Int32
-> Int32
-> IO ()
type C_PixbufLoaderSizePreparedCallback =
Ptr PixbufLoader ->
Int32 ->
Int32 ->
Ptr () ->
IO ()
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
forall a b. Coercible a b => a -> b
Coerce.coerce PixbufLoader
gi'self) Int32
width Int32
height
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 a. IO a -> m a
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
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 a. IO a -> m a
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.31/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, DK.Type)])
#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, DK.Type)])
#endif
foreign import ccall "gdk_pixbuf_loader_new" gdk_pixbuf_loader_new ::
IO (Ptr PixbufLoader)
pixbufLoaderNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m PixbufLoader
pixbufLoaderNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m PixbufLoader
pixbufLoaderNew = IO PixbufLoader -> m PixbufLoader
forall a. IO a -> m a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PixbufLoader
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gdk_pixbuf_loader_new_with_mime_type" gdk_pixbuf_loader_new_with_mime_type ::
CString ->
Ptr (Ptr GError) ->
IO (Ptr PixbufLoader)
pixbufLoaderNewWithMimeType ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> m PixbufLoader
pixbufLoaderNewWithMimeType :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m PixbufLoader
pixbufLoaderNewWithMimeType Text
mimeType = IO PixbufLoader -> m PixbufLoader
forall a. IO a -> m a
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 a. a -> IO a
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
foreign import ccall "gdk_pixbuf_loader_new_with_type" gdk_pixbuf_loader_new_with_type ::
CString ->
Ptr (Ptr GError) ->
IO (Ptr PixbufLoader)
pixbufLoaderNewWithType ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> m PixbufLoader
pixbufLoaderNewWithType :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m PixbufLoader
pixbufLoaderNewWithType Text
imageType = IO PixbufLoader -> m PixbufLoader
forall a. IO a -> m a
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 a. a -> IO a
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
foreign import ccall "gdk_pixbuf_loader_close" gdk_pixbuf_loader_close ::
Ptr PixbufLoader ->
Ptr (Ptr GError) ->
IO CInt
pixbufLoaderClose ::
(B.CallStack.HasCallStack, MonadIO m, IsPixbufLoader a) =>
a
-> m ()
pixbufLoaderClose :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbufLoader a) =>
a -> m ()
pixbufLoaderClose a
loader = 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 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 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)
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.31/docs/GI-GdkPixbuf-Objects-PixbufLoader.html#v:pixbufLoaderClose"
})
#endif
foreign import ccall "gdk_pixbuf_loader_get_animation" gdk_pixbuf_loader_get_animation ::
Ptr PixbufLoader ->
IO (Ptr GdkPixbuf.PixbufAnimation.PixbufAnimation)
pixbufLoaderGetAnimation ::
(B.CallStack.HasCallStack, MonadIO m, IsPixbufLoader a) =>
a
-> m (Maybe GdkPixbuf.PixbufAnimation.PixbufAnimation)
pixbufLoaderGetAnimation :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbufLoader a) =>
a -> m (Maybe PixbufAnimation)
pixbufLoaderGetAnimation a
loader = IO (Maybe PixbufAnimation) -> m (Maybe PixbufAnimation)
forall a. IO a -> m a
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 a. a -> IO a
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 a. a -> IO a
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.31/docs/GI-GdkPixbuf-Objects-PixbufLoader.html#v:pixbufLoaderGetAnimation"
})
#endif
foreign import ccall "gdk_pixbuf_loader_get_format" gdk_pixbuf_loader_get_format ::
Ptr PixbufLoader ->
IO (Ptr GdkPixbuf.PixbufFormat.PixbufFormat)
pixbufLoaderGetFormat ::
(B.CallStack.HasCallStack, MonadIO m, IsPixbufLoader a) =>
a
-> m (Maybe GdkPixbuf.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 a. IO a -> m a
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 a. a -> IO a
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 a. a -> IO a
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.31/docs/GI-GdkPixbuf-Objects-PixbufLoader.html#v:pixbufLoaderGetFormat"
})
#endif
foreign import ccall "gdk_pixbuf_loader_get_pixbuf" gdk_pixbuf_loader_get_pixbuf ::
Ptr PixbufLoader ->
IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)
pixbufLoaderGetPixbuf ::
(B.CallStack.HasCallStack, MonadIO m, IsPixbufLoader a) =>
a
-> m (Maybe GdkPixbuf.Pixbuf.Pixbuf)
pixbufLoaderGetPixbuf :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbufLoader a) =>
a -> m (Maybe Pixbuf)
pixbufLoaderGetPixbuf a
loader = 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 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 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
loader
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 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.31/docs/GI-GdkPixbuf-Objects-PixbufLoader.html#v:pixbufLoaderGetPixbuf"
})
#endif
foreign import ccall "gdk_pixbuf_loader_set_size" gdk_pixbuf_loader_set_size ::
Ptr PixbufLoader ->
Int32 ->
Int32 ->
IO ()
pixbufLoaderSetSize ::
(B.CallStack.HasCallStack, MonadIO m, IsPixbufLoader a) =>
a
-> Int32
-> Int32
-> m ()
pixbufLoaderSetSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbufLoader a) =>
a -> Int32 -> Int32 -> m ()
pixbufLoaderSetSize a
loader Int32
width Int32
height = 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 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 a. a -> IO a
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.31/docs/GI-GdkPixbuf-Objects-PixbufLoader.html#v:pixbufLoaderSetSize"
})
#endif
foreign import ccall "gdk_pixbuf_loader_write" gdk_pixbuf_loader_write ::
Ptr PixbufLoader ->
Ptr Word8 ->
Word64 ->
Ptr (Ptr GError) ->
IO CInt
pixbufLoaderWrite ::
(B.CallStack.HasCallStack, MonadIO m, IsPixbufLoader a) =>
a
-> ByteString
-> m ()
pixbufLoaderWrite :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbufLoader a) =>
a -> ByteString -> m ()
pixbufLoaderWrite a
loader ByteString
buf = 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
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 a. a -> IO a
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.31/docs/GI-GdkPixbuf-Objects-PixbufLoader.html#v:pixbufLoaderWrite"
})
#endif
foreign import ccall "gdk_pixbuf_loader_write_bytes" gdk_pixbuf_loader_write_bytes ::
Ptr PixbufLoader ->
Ptr GLib.Bytes.Bytes ->
Ptr (Ptr GError) ->
IO CInt
pixbufLoaderWriteBytes ::
(B.CallStack.HasCallStack, MonadIO m, IsPixbufLoader a) =>
a
-> GLib.Bytes.Bytes
-> m ()
pixbufLoaderWriteBytes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbufLoader a) =>
a -> Bytes -> m ()
pixbufLoaderWriteBytes a
loader Bytes
buffer = 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 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 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)
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.31/docs/GI-GdkPixbuf-Objects-PixbufLoader.html#v:pixbufLoaderWriteBytes"
})
#endif