{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GdkPixbuf.Objects.PixbufAnimationIter
(
PixbufAnimationIter(..) ,
IsPixbufAnimationIter ,
toPixbufAnimationIter ,
#if defined(ENABLE_OVERLOADING)
ResolvePixbufAnimationIterMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
PixbufAnimationIterAdvanceMethodInfo ,
#endif
pixbufAnimationIterAdvance ,
#if defined(ENABLE_OVERLOADING)
PixbufAnimationIterGetDelayTimeMethodInfo,
#endif
pixbufAnimationIterGetDelayTime ,
#if defined(ENABLE_OVERLOADING)
PixbufAnimationIterGetPixbufMethodInfo ,
#endif
pixbufAnimationIterGetPixbuf ,
#if defined(ENABLE_OVERLOADING)
PixbufAnimationIterOnCurrentlyLoadingFrameMethodInfo,
#endif
pixbufAnimationIterOnCurrentlyLoadingFrame,
) 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.TimeVal as GLib.TimeVal
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
newtype PixbufAnimationIter = PixbufAnimationIter (SP.ManagedPtr PixbufAnimationIter)
deriving (PixbufAnimationIter -> PixbufAnimationIter -> Bool
(PixbufAnimationIter -> PixbufAnimationIter -> Bool)
-> (PixbufAnimationIter -> PixbufAnimationIter -> Bool)
-> Eq PixbufAnimationIter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PixbufAnimationIter -> PixbufAnimationIter -> Bool
== :: PixbufAnimationIter -> PixbufAnimationIter -> Bool
$c/= :: PixbufAnimationIter -> PixbufAnimationIter -> Bool
/= :: PixbufAnimationIter -> PixbufAnimationIter -> Bool
Eq)
instance SP.ManagedPtrNewtype PixbufAnimationIter where
toManagedPtr :: PixbufAnimationIter -> ManagedPtr PixbufAnimationIter
toManagedPtr (PixbufAnimationIter ManagedPtr PixbufAnimationIter
p) = ManagedPtr PixbufAnimationIter
p
foreign import ccall "gdk_pixbuf_animation_iter_get_type"
c_gdk_pixbuf_animation_iter_get_type :: IO B.Types.GType
instance B.Types.TypedObject PixbufAnimationIter where
glibType :: IO GType
glibType = IO GType
c_gdk_pixbuf_animation_iter_get_type
instance B.Types.GObject PixbufAnimationIter
class (SP.GObject o, O.IsDescendantOf PixbufAnimationIter o) => IsPixbufAnimationIter o
instance (SP.GObject o, O.IsDescendantOf PixbufAnimationIter o) => IsPixbufAnimationIter o
instance O.HasParentTypes PixbufAnimationIter
type instance O.ParentTypes PixbufAnimationIter = '[GObject.Object.Object]
toPixbufAnimationIter :: (MIO.MonadIO m, IsPixbufAnimationIter o) => o -> m PixbufAnimationIter
toPixbufAnimationIter :: forall (m :: * -> *) o.
(MonadIO m, IsPixbufAnimationIter o) =>
o -> m PixbufAnimationIter
toPixbufAnimationIter = IO PixbufAnimationIter -> m PixbufAnimationIter
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO PixbufAnimationIter -> m PixbufAnimationIter)
-> (o -> IO PixbufAnimationIter) -> o -> m PixbufAnimationIter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr PixbufAnimationIter -> PixbufAnimationIter)
-> o -> IO PixbufAnimationIter
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr PixbufAnimationIter -> PixbufAnimationIter
PixbufAnimationIter
instance B.GValue.IsGValue (Maybe PixbufAnimationIter) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gdk_pixbuf_animation_iter_get_type
gvalueSet_ :: Ptr GValue -> Maybe PixbufAnimationIter -> IO ()
gvalueSet_ Ptr GValue
gv Maybe PixbufAnimationIter
P.Nothing = Ptr GValue -> Ptr PixbufAnimationIter -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr PixbufAnimationIter
forall a. Ptr a
FP.nullPtr :: FP.Ptr PixbufAnimationIter)
gvalueSet_ Ptr GValue
gv (P.Just PixbufAnimationIter
obj) = PixbufAnimationIter -> (Ptr PixbufAnimationIter -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr PixbufAnimationIter
obj (Ptr GValue -> Ptr PixbufAnimationIter -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe PixbufAnimationIter)
gvalueGet_ Ptr GValue
gv = do
Ptr PixbufAnimationIter
ptr <- Ptr GValue -> IO (Ptr PixbufAnimationIter)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr PixbufAnimationIter)
if Ptr PixbufAnimationIter
ptr Ptr PixbufAnimationIter -> Ptr PixbufAnimationIter -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr PixbufAnimationIter
forall a. Ptr a
FP.nullPtr
then PixbufAnimationIter -> Maybe PixbufAnimationIter
forall a. a -> Maybe a
P.Just (PixbufAnimationIter -> Maybe PixbufAnimationIter)
-> IO PixbufAnimationIter -> IO (Maybe PixbufAnimationIter)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr PixbufAnimationIter -> PixbufAnimationIter)
-> Ptr PixbufAnimationIter -> IO PixbufAnimationIter
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr PixbufAnimationIter -> PixbufAnimationIter
PixbufAnimationIter Ptr PixbufAnimationIter
ptr
else Maybe PixbufAnimationIter -> IO (Maybe PixbufAnimationIter)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PixbufAnimationIter
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolvePixbufAnimationIterMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolvePixbufAnimationIterMethod "advance" o = PixbufAnimationIterAdvanceMethodInfo
ResolvePixbufAnimationIterMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolvePixbufAnimationIterMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolvePixbufAnimationIterMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolvePixbufAnimationIterMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolvePixbufAnimationIterMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolvePixbufAnimationIterMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolvePixbufAnimationIterMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolvePixbufAnimationIterMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolvePixbufAnimationIterMethod "onCurrentlyLoadingFrame" o = PixbufAnimationIterOnCurrentlyLoadingFrameMethodInfo
ResolvePixbufAnimationIterMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolvePixbufAnimationIterMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolvePixbufAnimationIterMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolvePixbufAnimationIterMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolvePixbufAnimationIterMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolvePixbufAnimationIterMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolvePixbufAnimationIterMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolvePixbufAnimationIterMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolvePixbufAnimationIterMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolvePixbufAnimationIterMethod "getDelayTime" o = PixbufAnimationIterGetDelayTimeMethodInfo
ResolvePixbufAnimationIterMethod "getPixbuf" o = PixbufAnimationIterGetPixbufMethodInfo
ResolvePixbufAnimationIterMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolvePixbufAnimationIterMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolvePixbufAnimationIterMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolvePixbufAnimationIterMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolvePixbufAnimationIterMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolvePixbufAnimationIterMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolvePixbufAnimationIterMethod t PixbufAnimationIter, O.OverloadedMethod info PixbufAnimationIter p) => OL.IsLabel t (PixbufAnimationIter -> 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 ~ ResolvePixbufAnimationIterMethod t PixbufAnimationIter, O.OverloadedMethod info PixbufAnimationIter p, R.HasField t PixbufAnimationIter p) => R.HasField t PixbufAnimationIter p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolvePixbufAnimationIterMethod t PixbufAnimationIter, O.OverloadedMethodInfo info PixbufAnimationIter) => OL.IsLabel t (O.MethodProxy info PixbufAnimationIter) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList PixbufAnimationIter
type instance O.AttributeList PixbufAnimationIter = PixbufAnimationIterAttributeList
type PixbufAnimationIterAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList PixbufAnimationIter = PixbufAnimationIterSignalList
type PixbufAnimationIterSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gdk_pixbuf_animation_iter_advance" gdk_pixbuf_animation_iter_advance ::
Ptr PixbufAnimationIter ->
Ptr GLib.TimeVal.TimeVal ->
IO CInt
pixbufAnimationIterAdvance ::
(B.CallStack.HasCallStack, MonadIO m, IsPixbufAnimationIter a) =>
a
-> Maybe (GLib.TimeVal.TimeVal)
-> m Bool
pixbufAnimationIterAdvance :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbufAnimationIter a) =>
a -> Maybe TimeVal -> m Bool
pixbufAnimationIterAdvance a
iter Maybe TimeVal
currentTime = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr PixbufAnimationIter
iter' <- a -> IO (Ptr PixbufAnimationIter)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iter
Ptr TimeVal
maybeCurrentTime <- case Maybe TimeVal
currentTime of
Maybe TimeVal
Nothing -> Ptr TimeVal -> IO (Ptr TimeVal)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TimeVal
forall a. Ptr a
nullPtr
Just TimeVal
jCurrentTime -> do
Ptr TimeVal
jCurrentTime' <- TimeVal -> IO (Ptr TimeVal)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TimeVal
jCurrentTime
Ptr TimeVal -> IO (Ptr TimeVal)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TimeVal
jCurrentTime'
CInt
result <- Ptr PixbufAnimationIter -> Ptr TimeVal -> IO CInt
gdk_pixbuf_animation_iter_advance Ptr PixbufAnimationIter
iter' Ptr TimeVal
maybeCurrentTime
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iter
Maybe TimeVal -> (TimeVal -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe TimeVal
currentTime TimeVal -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data PixbufAnimationIterAdvanceMethodInfo
instance (signature ~ (Maybe (GLib.TimeVal.TimeVal) -> m Bool), MonadIO m, IsPixbufAnimationIter a) => O.OverloadedMethod PixbufAnimationIterAdvanceMethodInfo a signature where
overloadedMethod = pixbufAnimationIterAdvance
instance O.OverloadedMethodInfo PixbufAnimationIterAdvanceMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GdkPixbuf.Objects.PixbufAnimationIter.pixbufAnimationIterAdvance",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.31/docs/GI-GdkPixbuf-Objects-PixbufAnimationIter.html#v:pixbufAnimationIterAdvance"
})
#endif
foreign import ccall "gdk_pixbuf_animation_iter_get_delay_time" gdk_pixbuf_animation_iter_get_delay_time ::
Ptr PixbufAnimationIter ->
IO Int32
pixbufAnimationIterGetDelayTime ::
(B.CallStack.HasCallStack, MonadIO m, IsPixbufAnimationIter a) =>
a
-> m Int32
pixbufAnimationIterGetDelayTime :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbufAnimationIter a) =>
a -> m Int32
pixbufAnimationIterGetDelayTime a
iter = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
Ptr PixbufAnimationIter
iter' <- a -> IO (Ptr PixbufAnimationIter)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iter
Int32
result <- Ptr PixbufAnimationIter -> IO Int32
gdk_pixbuf_animation_iter_get_delay_time Ptr PixbufAnimationIter
iter'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iter
Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data PixbufAnimationIterGetDelayTimeMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsPixbufAnimationIter a) => O.OverloadedMethod PixbufAnimationIterGetDelayTimeMethodInfo a signature where
overloadedMethod = pixbufAnimationIterGetDelayTime
instance O.OverloadedMethodInfo PixbufAnimationIterGetDelayTimeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GdkPixbuf.Objects.PixbufAnimationIter.pixbufAnimationIterGetDelayTime",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.31/docs/GI-GdkPixbuf-Objects-PixbufAnimationIter.html#v:pixbufAnimationIterGetDelayTime"
})
#endif
foreign import ccall "gdk_pixbuf_animation_iter_get_pixbuf" gdk_pixbuf_animation_iter_get_pixbuf ::
Ptr PixbufAnimationIter ->
IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)
pixbufAnimationIterGetPixbuf ::
(B.CallStack.HasCallStack, MonadIO m, IsPixbufAnimationIter a) =>
a
-> m GdkPixbuf.Pixbuf.Pixbuf
pixbufAnimationIterGetPixbuf :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbufAnimationIter a) =>
a -> m Pixbuf
pixbufAnimationIterGetPixbuf a
iter = IO Pixbuf -> m Pixbuf
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Pixbuf -> m Pixbuf) -> IO Pixbuf -> m Pixbuf
forall a b. (a -> b) -> a -> b
$ do
Ptr PixbufAnimationIter
iter' <- a -> IO (Ptr PixbufAnimationIter)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iter
Ptr Pixbuf
result <- Ptr PixbufAnimationIter -> IO (Ptr Pixbuf)
gdk_pixbuf_animation_iter_get_pixbuf Ptr PixbufAnimationIter
iter'
Text -> Ptr Pixbuf -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pixbufAnimationIterGetPixbuf" Ptr Pixbuf
result
Pixbuf
result' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Pixbuf -> Pixbuf
GdkPixbuf.Pixbuf.Pixbuf) Ptr Pixbuf
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iter
Pixbuf -> IO Pixbuf
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result'
#if defined(ENABLE_OVERLOADING)
data PixbufAnimationIterGetPixbufMethodInfo
instance (signature ~ (m GdkPixbuf.Pixbuf.Pixbuf), MonadIO m, IsPixbufAnimationIter a) => O.OverloadedMethod PixbufAnimationIterGetPixbufMethodInfo a signature where
overloadedMethod = pixbufAnimationIterGetPixbuf
instance O.OverloadedMethodInfo PixbufAnimationIterGetPixbufMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GdkPixbuf.Objects.PixbufAnimationIter.pixbufAnimationIterGetPixbuf",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.31/docs/GI-GdkPixbuf-Objects-PixbufAnimationIter.html#v:pixbufAnimationIterGetPixbuf"
})
#endif
foreign import ccall "gdk_pixbuf_animation_iter_on_currently_loading_frame" gdk_pixbuf_animation_iter_on_currently_loading_frame ::
Ptr PixbufAnimationIter ->
IO CInt
pixbufAnimationIterOnCurrentlyLoadingFrame ::
(B.CallStack.HasCallStack, MonadIO m, IsPixbufAnimationIter a) =>
a
-> m Bool
pixbufAnimationIterOnCurrentlyLoadingFrame :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbufAnimationIter a) =>
a -> m Bool
pixbufAnimationIterOnCurrentlyLoadingFrame a
iter = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr PixbufAnimationIter
iter' <- a -> IO (Ptr PixbufAnimationIter)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iter
CInt
result <- Ptr PixbufAnimationIter -> IO CInt
gdk_pixbuf_animation_iter_on_currently_loading_frame Ptr PixbufAnimationIter
iter'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iter
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data PixbufAnimationIterOnCurrentlyLoadingFrameMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPixbufAnimationIter a) => O.OverloadedMethod PixbufAnimationIterOnCurrentlyLoadingFrameMethodInfo a signature where
overloadedMethod = pixbufAnimationIterOnCurrentlyLoadingFrame
instance O.OverloadedMethodInfo PixbufAnimationIterOnCurrentlyLoadingFrameMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GdkPixbuf.Objects.PixbufAnimationIter.pixbufAnimationIterOnCurrentlyLoadingFrame",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.31/docs/GI-GdkPixbuf-Objects-PixbufAnimationIter.html#v:pixbufAnimationIterOnCurrentlyLoadingFrame"
})
#endif