{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- An opaque object 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                   ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [advance]("GI.GdkPixbuf.Objects.PixbufAnimationIter#g:method:advance"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [onCurrentlyLoadingFrame]("GI.GdkPixbuf.Objects.PixbufAnimationIter#g:method:onCurrentlyLoadingFrame"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDelayTime]("GI.GdkPixbuf.Objects.PixbufAnimationIter#g:method:getDelayTime"), [getPixbuf]("GI.GdkPixbuf.Objects.PixbufAnimationIter#g:method:getPixbuf"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

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

import qualified GI.GLib.Structs.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 (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

-- | Type class for types which can be safely cast to `PixbufAnimationIter`, for instance with `toPixbufAnimationIter`.
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]

-- | Cast to `PixbufAnimationIter`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
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

-- | Convert 'PixbufAnimationIter' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe 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 :: *) :: * 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, *)])
#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 @NULL@ 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 @FALSE@, there\'s no need to update the animation
-- display, assuming the display had been rendered prior to advancing;
-- if @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:__ @TRUE@ if the image may need updating
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.29/docs/GI-GdkPixbuf-Objects-PixbufAnimationIter.html#v: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.
-- 
-- The @g_timeout_add()@ function 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 :: 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.29/docs/GI-GdkPixbuf-Objects-PixbufAnimationIter.html#v: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 :: 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.29/docs/GI-GdkPixbuf-Objects-PixbufAnimationIter.html#v: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.
-- 
-- The @::area_updated@ signal is emitted for an area of the frame currently
-- streaming in to the loader. So if you\'re on the currently loading frame,
-- you will 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:__ @TRUE@ if the frame we\'re on is partially loaded, or the last frame
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.29/docs/GI-GdkPixbuf-Objects-PixbufAnimationIter.html#v:pixbufAnimationIterOnCurrentlyLoadingFrame"
        })


#endif