{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- An opaque struct representing an iterator which points to a
-- certain position in an animation.

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

module GI.GdkPixbuf.Objects.PixbufAnimationIter
    ( 

-- * Exported types
    PixbufAnimationIter(..)                 ,
    IsPixbufAnimationIter                   ,
    toPixbufAnimationIter                   ,
    noPixbufAnimationIter                   ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolvePixbufAnimationIterMethod        ,
#endif


-- ** advance #method:advance#

#if defined(ENABLE_OVERLOADING)
    PixbufAnimationIterAdvanceMethodInfo    ,
#endif
    pixbufAnimationIterAdvance              ,


-- ** getDelayTime #method:getDelayTime#

#if defined(ENABLE_OVERLOADING)
    PixbufAnimationIterGetDelayTimeMethodInfo,
#endif
    pixbufAnimationIterGetDelayTime         ,


-- ** getPixbuf #method:getPixbuf#

#if defined(ENABLE_OVERLOADING)
    PixbufAnimationIterGetPixbufMethodInfo  ,
#endif
    pixbufAnimationIterGetPixbuf            ,


-- ** onCurrentlyLoadingFrame #method:onCurrentlyLoadingFrame#

#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.ManagedPtr as B.ManagedPtr
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 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 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

-- | Memory-managed wrapper type.
newtype PixbufAnimationIter = PixbufAnimationIter (ManagedPtr PixbufAnimationIter)
    deriving (PixbufAnimationIter -> PixbufAnimationIter -> Bool
(PixbufAnimationIter -> PixbufAnimationIter -> Bool)
-> (PixbufAnimationIter -> PixbufAnimationIter -> Bool)
-> Eq PixbufAnimationIter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PixbufAnimationIter -> PixbufAnimationIter -> Bool
$c/= :: PixbufAnimationIter -> PixbufAnimationIter -> Bool
== :: PixbufAnimationIter -> PixbufAnimationIter -> Bool
$c== :: PixbufAnimationIter -> PixbufAnimationIter -> Bool
Eq)
foreign import ccall "gdk_pixbuf_animation_iter_get_type"
    c_gdk_pixbuf_animation_iter_get_type :: IO GType

instance GObject PixbufAnimationIter where
    gobjectType :: IO GType
gobjectType = IO GType
c_gdk_pixbuf_animation_iter_get_type
    

-- | Convert 'PixbufAnimationIter' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue PixbufAnimationIter where
    toGValue :: PixbufAnimationIter -> IO GValue
toGValue o :: PixbufAnimationIter
o = do
        GType
gtype <- IO GType
c_gdk_pixbuf_animation_iter_get_type
        PixbufAnimationIter
-> (Ptr PixbufAnimationIter -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr PixbufAnimationIter
o (GType
-> (GValue -> Ptr PixbufAnimationIter -> IO ())
-> Ptr PixbufAnimationIter
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr PixbufAnimationIter -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO PixbufAnimationIter
fromGValue gv :: GValue
gv = do
        Ptr PixbufAnimationIter
ptr <- GValue -> IO (Ptr PixbufAnimationIter)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr PixbufAnimationIter)
        (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
        
    

-- | Type class for types which can be safely cast to `PixbufAnimationIter`, for instance with `toPixbufAnimationIter`.
class (GObject o, O.IsDescendantOf PixbufAnimationIter o) => IsPixbufAnimationIter o
instance (GObject o, O.IsDescendantOf PixbufAnimationIter o) => IsPixbufAnimationIter o

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

-- | Cast to `PixbufAnimationIter`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toPixbufAnimationIter :: (MonadIO m, IsPixbufAnimationIter o) => o -> m PixbufAnimationIter
toPixbufAnimationIter :: o -> m PixbufAnimationIter
toPixbufAnimationIter = IO PixbufAnimationIter -> m PixbufAnimationIter
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr PixbufAnimationIter -> PixbufAnimationIter
PixbufAnimationIter

-- | A convenience alias for `Nothing` :: `Maybe` `PixbufAnimationIter`.
noPixbufAnimationIter :: Maybe PixbufAnimationIter
noPixbufAnimationIter :: Maybe PixbufAnimationIter
noPixbufAnimationIter = Maybe PixbufAnimationIter
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolvePixbufAnimationIterMethod (t :: Symbol) (o :: *) :: * 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.MethodInfo 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

#endif

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

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

-- method PixbufAnimationIter::advance
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface
--                 Name { namespace = "GdkPixbuf" , name = "PixbufAnimationIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkPixbufAnimationIter"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "current_time"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "TimeVal" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "current time" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_animation_iter_advance" gdk_pixbuf_animation_iter_advance :: 
    Ptr PixbufAnimationIter ->              -- iter : TInterface (Name {namespace = "GdkPixbuf", name = "PixbufAnimationIter"})
    Ptr GLib.TimeVal.TimeVal ->             -- current_time : TInterface (Name {namespace = "GLib", name = "TimeVal"})
    IO CInt

-- | Possibly advances an animation to a new frame. Chooses the frame based
-- on the start time passed to 'GI.GdkPixbuf.Objects.PixbufAnimation.pixbufAnimationGetIter'.
-- 
-- /@currentTime@/ would normally come from 'GI.GLib.Functions.getCurrentTime', and
-- must be greater than or equal to the time passed to
-- 'GI.GdkPixbuf.Objects.PixbufAnimation.pixbufAnimationGetIter', and must increase or remain
-- unchanged each time 'GI.GdkPixbuf.Objects.PixbufAnimationIter.pixbufAnimationIterGetPixbuf' is
-- called. That is, you can\'t go backward in time; animations only
-- play forward.
-- 
-- As a shortcut, pass 'P.Nothing' for the current time and 'GI.GLib.Functions.getCurrentTime'
-- will be invoked on your behalf. So you only need to explicitly pass
-- /@currentTime@/ if you\'re doing something odd like playing the animation
-- at double speed.
-- 
-- If this function returns 'P.False', there\'s no need to update the animation
-- display, assuming the display had been rendered prior to advancing;
-- if 'P.True', you need to call 'GI.GdkPixbuf.Objects.PixbufAnimationIter.pixbufAnimationIterGetPixbuf'
-- and update the display with the new pixbuf.
pixbufAnimationIterAdvance ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbufAnimationIter a) =>
    a
    -- ^ /@iter@/: a t'GI.GdkPixbuf.Objects.PixbufAnimationIter.PixbufAnimationIter'
    -> Maybe (GLib.TimeVal.TimeVal)
    -- ^ /@currentTime@/: current time
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the image may need updating
pixbufAnimationIterAdvance :: a -> Maybe TimeVal -> m Bool
pixbufAnimationIterAdvance iter :: a
iter currentTime :: Maybe TimeVal
currentTime = IO Bool -> m Bool
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
        Nothing -> Ptr TimeVal -> IO (Ptr TimeVal)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TimeVal
forall a. Ptr a
nullPtr
        Just jCurrentTime :: 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 (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
/= 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 (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.MethodInfo PixbufAnimationIterAdvanceMethodInfo a signature where
    overloadedMethod = pixbufAnimationIterAdvance

#endif

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

foreign import ccall "gdk_pixbuf_animation_iter_get_delay_time" gdk_pixbuf_animation_iter_get_delay_time :: 
    Ptr PixbufAnimationIter ->              -- iter : TInterface (Name {namespace = "GdkPixbuf", name = "PixbufAnimationIter"})
    IO Int32

-- | Gets the number of milliseconds the current pixbuf should be displayed,
-- or -1 if the current pixbuf should be displayed forever. @/g_timeout_add()/@
-- conveniently takes a timeout in milliseconds, so you can use a timeout
-- to schedule the next update.
-- 
-- Note that some formats, like GIF, might clamp the timeout values in the
-- image file to avoid updates that are just too quick. The minimum timeout
-- for GIF images is currently 20 milliseconds.
pixbufAnimationIterGetDelayTime ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbufAnimationIter a) =>
    a
    -- ^ /@iter@/: an animation iterator
    -> m Int32
    -- ^ __Returns:__ delay time in milliseconds (thousandths of a second)
pixbufAnimationIterGetDelayTime :: a -> m Int32
pixbufAnimationIterGetDelayTime iter :: a
iter = IO Int32 -> m Int32
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 (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.MethodInfo PixbufAnimationIterGetDelayTimeMethodInfo a signature where
    overloadedMethod = pixbufAnimationIterGetDelayTime

#endif

-- method PixbufAnimationIter::get_pixbuf
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface
--                 Name { namespace = "GdkPixbuf" , name = "PixbufAnimationIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an animation iterator"
--                 , 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_animation_iter_get_pixbuf" gdk_pixbuf_animation_iter_get_pixbuf :: 
    Ptr PixbufAnimationIter ->              -- iter : TInterface (Name {namespace = "GdkPixbuf", name = "PixbufAnimationIter"})
    IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)

-- | Gets the current pixbuf which should be displayed; the pixbuf might not
-- be the same size as the animation itself
-- ('GI.GdkPixbuf.Objects.PixbufAnimation.pixbufAnimationGetWidth', 'GI.GdkPixbuf.Objects.PixbufAnimation.pixbufAnimationGetHeight').
-- This pixbuf should be displayed for
-- 'GI.GdkPixbuf.Objects.PixbufAnimationIter.pixbufAnimationIterGetDelayTime' milliseconds. The caller
-- of this function does not own a reference to the returned pixbuf;
-- the returned pixbuf will become invalid when the iterator advances
-- to the next frame, which may happen anytime you call
-- 'GI.GdkPixbuf.Objects.PixbufAnimationIter.pixbufAnimationIterAdvance'. Copy the pixbuf to keep it
-- (don\'t just add a reference), as it may get recycled as you advance
-- the iterator.
pixbufAnimationIterGetPixbuf ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbufAnimationIter a) =>
    a
    -- ^ /@iter@/: an animation iterator
    -> m GdkPixbuf.Pixbuf.Pixbuf
    -- ^ __Returns:__ the pixbuf to be displayed
pixbufAnimationIterGetPixbuf :: a -> m Pixbuf
pixbufAnimationIterGetPixbuf iter :: a
iter = IO Pixbuf -> m Pixbuf
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 "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 (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.MethodInfo PixbufAnimationIterGetPixbufMethodInfo a signature where
    overloadedMethod = pixbufAnimationIterGetPixbuf

#endif

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

foreign import ccall "gdk_pixbuf_animation_iter_on_currently_loading_frame" gdk_pixbuf_animation_iter_on_currently_loading_frame :: 
    Ptr PixbufAnimationIter ->              -- iter : TInterface (Name {namespace = "GdkPixbuf", name = "PixbufAnimationIter"})
    IO CInt

-- | Used to determine how to respond to the area_updated signal on
-- t'GI.GdkPixbuf.Objects.PixbufLoader.PixbufLoader' when loading an animation. area_updated is emitted
-- for an area of the frame currently streaming in to the loader. So if
-- you\'re on the currently loading frame, you need to redraw the screen for
-- the updated area.
pixbufAnimationIterOnCurrentlyLoadingFrame ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbufAnimationIter a) =>
    a
    -- ^ /@iter@/: a t'GI.GdkPixbuf.Objects.PixbufAnimationIter.PixbufAnimationIter'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the frame we\'re on is partially loaded, or the last frame
pixbufAnimationIterOnCurrentlyLoadingFrame :: a -> m Bool
pixbufAnimationIterOnCurrentlyLoadingFrame iter :: a
iter = IO Bool -> m Bool
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
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iter
    Bool -> IO Bool
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.MethodInfo PixbufAnimationIterOnCurrentlyLoadingFrameMethodInfo a signature where
    overloadedMethod = pixbufAnimationIterOnCurrentlyLoadingFrame

#endif