{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- An opaque struct representing a simple animation.

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

module GI.GdkPixbuf.Objects.PixbufSimpleAnim
    ( 

-- * Exported types
    PixbufSimpleAnim(..)                    ,
    IsPixbufSimpleAnim                      ,
    toPixbufSimpleAnim                      ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [addFrame]("GI.GdkPixbuf.Objects.PixbufSimpleAnim#g:method:addFrame"), [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"), [isStaticImage]("GI.GdkPixbuf.Objects.PixbufAnimation#g:method:isStaticImage"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getHeight]("GI.GdkPixbuf.Objects.PixbufAnimation#g:method:getHeight"), [getIter]("GI.GdkPixbuf.Objects.PixbufAnimation#g:method:getIter"), [getLoop]("GI.GdkPixbuf.Objects.PixbufSimpleAnim#g:method:getLoop"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getStaticImage]("GI.GdkPixbuf.Objects.PixbufAnimation#g:method:getStaticImage"), [getWidth]("GI.GdkPixbuf.Objects.PixbufAnimation#g:method:getWidth").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setLoop]("GI.GdkPixbuf.Objects.PixbufSimpleAnim#g:method:setLoop"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolvePixbufSimpleAnimMethod           ,
#endif

-- ** addFrame #method:addFrame#

#if defined(ENABLE_OVERLOADING)
    PixbufSimpleAnimAddFrameMethodInfo      ,
#endif
    pixbufSimpleAnimAddFrame                ,


-- ** getLoop #method:getLoop#

#if defined(ENABLE_OVERLOADING)
    PixbufSimpleAnimGetLoopMethodInfo       ,
#endif
    pixbufSimpleAnimGetLoop                 ,


-- ** new #method:new#

    pixbufSimpleAnimNew                     ,


-- ** setLoop #method:setLoop#

#if defined(ENABLE_OVERLOADING)
    PixbufSimpleAnimSetLoopMethodInfo       ,
#endif
    pixbufSimpleAnimSetLoop                 ,




 -- * Properties


-- ** loop #attr:loop#
-- | Whether the animation should loop when it reaches the end.
-- 
-- /Since: 2.18/

#if defined(ENABLE_OVERLOADING)
    PixbufSimpleAnimLoopPropertyInfo        ,
#endif
    constructPixbufSimpleAnimLoop           ,
    getPixbufSimpleAnimLoop                 ,
#if defined(ENABLE_OVERLOADING)
    pixbufSimpleAnimLoop                    ,
#endif
    setPixbufSimpleAnimLoop                 ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

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

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

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

foreign import ccall "gdk_pixbuf_simple_anim_get_type"
    c_gdk_pixbuf_simple_anim_get_type :: IO B.Types.GType

instance B.Types.TypedObject PixbufSimpleAnim where
    glibType :: IO GType
glibType = IO GType
c_gdk_pixbuf_simple_anim_get_type

instance B.Types.GObject PixbufSimpleAnim

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

instance O.HasParentTypes PixbufSimpleAnim
type instance O.ParentTypes PixbufSimpleAnim = '[GdkPixbuf.PixbufAnimation.PixbufAnimation, GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolvePixbufSimpleAnimMethod (t :: Symbol) (o :: *) :: * where
    ResolvePixbufSimpleAnimMethod "addFrame" o = PixbufSimpleAnimAddFrameMethodInfo
    ResolvePixbufSimpleAnimMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolvePixbufSimpleAnimMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolvePixbufSimpleAnimMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolvePixbufSimpleAnimMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolvePixbufSimpleAnimMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolvePixbufSimpleAnimMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolvePixbufSimpleAnimMethod "isStaticImage" o = GdkPixbuf.PixbufAnimation.PixbufAnimationIsStaticImageMethodInfo
    ResolvePixbufSimpleAnimMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolvePixbufSimpleAnimMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolvePixbufSimpleAnimMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolvePixbufSimpleAnimMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolvePixbufSimpleAnimMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolvePixbufSimpleAnimMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolvePixbufSimpleAnimMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolvePixbufSimpleAnimMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolvePixbufSimpleAnimMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolvePixbufSimpleAnimMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolvePixbufSimpleAnimMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolvePixbufSimpleAnimMethod "getHeight" o = GdkPixbuf.PixbufAnimation.PixbufAnimationGetHeightMethodInfo
    ResolvePixbufSimpleAnimMethod "getIter" o = GdkPixbuf.PixbufAnimation.PixbufAnimationGetIterMethodInfo
    ResolvePixbufSimpleAnimMethod "getLoop" o = PixbufSimpleAnimGetLoopMethodInfo
    ResolvePixbufSimpleAnimMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolvePixbufSimpleAnimMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolvePixbufSimpleAnimMethod "getStaticImage" o = GdkPixbuf.PixbufAnimation.PixbufAnimationGetStaticImageMethodInfo
    ResolvePixbufSimpleAnimMethod "getWidth" o = GdkPixbuf.PixbufAnimation.PixbufAnimationGetWidthMethodInfo
    ResolvePixbufSimpleAnimMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolvePixbufSimpleAnimMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolvePixbufSimpleAnimMethod "setLoop" o = PixbufSimpleAnimSetLoopMethodInfo
    ResolvePixbufSimpleAnimMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolvePixbufSimpleAnimMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- VVV Prop "loop"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@loop@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' pixbufSimpleAnim #loop
-- @
getPixbufSimpleAnimLoop :: (MonadIO m, IsPixbufSimpleAnim o) => o -> m Bool
getPixbufSimpleAnimLoop :: forall (m :: * -> *) o.
(MonadIO m, IsPixbufSimpleAnim o) =>
o -> m Bool
getPixbufSimpleAnimLoop o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"loop"

-- | Set the value of the “@loop@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' pixbufSimpleAnim [ #loop 'Data.GI.Base.Attributes.:=' value ]
-- @
setPixbufSimpleAnimLoop :: (MonadIO m, IsPixbufSimpleAnim o) => o -> Bool -> m ()
setPixbufSimpleAnimLoop :: forall (m :: * -> *) o.
(MonadIO m, IsPixbufSimpleAnim o) =>
o -> Bool -> m ()
setPixbufSimpleAnimLoop o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"loop" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@loop@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPixbufSimpleAnimLoop :: (IsPixbufSimpleAnim o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructPixbufSimpleAnimLoop :: forall o (m :: * -> *).
(IsPixbufSimpleAnim o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructPixbufSimpleAnimLoop Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"loop" Bool
val

#if defined(ENABLE_OVERLOADING)
data PixbufSimpleAnimLoopPropertyInfo
instance AttrInfo PixbufSimpleAnimLoopPropertyInfo where
    type AttrAllowedOps PixbufSimpleAnimLoopPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PixbufSimpleAnimLoopPropertyInfo = IsPixbufSimpleAnim
    type AttrSetTypeConstraint PixbufSimpleAnimLoopPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint PixbufSimpleAnimLoopPropertyInfo = (~) Bool
    type AttrTransferType PixbufSimpleAnimLoopPropertyInfo = Bool
    type AttrGetType PixbufSimpleAnimLoopPropertyInfo = Bool
    type AttrLabel PixbufSimpleAnimLoopPropertyInfo = "loop"
    type AttrOrigin PixbufSimpleAnimLoopPropertyInfo = PixbufSimpleAnim
    attrGet = getPixbufSimpleAnimLoop
    attrSet = setPixbufSimpleAnimLoop
    attrTransfer _ v = do
        return v
    attrConstruct = constructPixbufSimpleAnimLoop
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Objects.PixbufSimpleAnim.loop"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.28/docs/GI-GdkPixbuf-Objects-PixbufSimpleAnim.html#g:attr:loop"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList PixbufSimpleAnim
type instance O.AttributeList PixbufSimpleAnim = PixbufSimpleAnimAttributeList
type PixbufSimpleAnimAttributeList = ('[ '("loop", PixbufSimpleAnimLoopPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
pixbufSimpleAnimLoop :: AttrLabelProxy "loop"
pixbufSimpleAnimLoop = AttrLabelProxy

#endif

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

#endif

-- method PixbufSimpleAnim::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the width of the animation"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the height of the animation"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "rate"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the speed of the animation, in frames per second"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "GdkPixbuf" , name = "PixbufSimpleAnim" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_simple_anim_new" gdk_pixbuf_simple_anim_new :: 
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    CFloat ->                               -- rate : TBasicType TFloat
    IO (Ptr PixbufSimpleAnim)

-- | Creates a new, empty animation.
-- 
-- /Since: 2.8/
pixbufSimpleAnimNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Int32
    -- ^ /@width@/: the width of the animation
    -> Int32
    -- ^ /@height@/: the height of the animation
    -> Float
    -- ^ /@rate@/: the speed of the animation, in frames per second
    -> m PixbufSimpleAnim
    -- ^ __Returns:__ a newly allocated t'GI.GdkPixbuf.Objects.PixbufSimpleAnim.PixbufSimpleAnim'
pixbufSimpleAnimNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Int32 -> Int32 -> Float -> m PixbufSimpleAnim
pixbufSimpleAnimNew Int32
width Int32
height Float
rate = IO PixbufSimpleAnim -> m PixbufSimpleAnim
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PixbufSimpleAnim -> m PixbufSimpleAnim)
-> IO PixbufSimpleAnim -> m PixbufSimpleAnim
forall a b. (a -> b) -> a -> b
$ do
    let rate' :: CFloat
rate' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
rate
    Ptr PixbufSimpleAnim
result <- Int32 -> Int32 -> CFloat -> IO (Ptr PixbufSimpleAnim)
gdk_pixbuf_simple_anim_new Int32
width Int32
height CFloat
rate'
    Text -> Ptr PixbufSimpleAnim -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pixbufSimpleAnimNew" Ptr PixbufSimpleAnim
result
    PixbufSimpleAnim
result' <- ((ManagedPtr PixbufSimpleAnim -> PixbufSimpleAnim)
-> Ptr PixbufSimpleAnim -> IO PixbufSimpleAnim
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr PixbufSimpleAnim -> PixbufSimpleAnim
PixbufSimpleAnim) Ptr PixbufSimpleAnim
result
    PixbufSimpleAnim -> IO PixbufSimpleAnim
forall (m :: * -> *) a. Monad m => a -> m a
return PixbufSimpleAnim
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method PixbufSimpleAnim::add_frame
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "animation"
--           , argType =
--               TInterface
--                 Name { namespace = "GdkPixbuf" , name = "PixbufSimpleAnim" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkPixbufSimpleAnim"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the pixbuf to add" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_simple_anim_add_frame" gdk_pixbuf_simple_anim_add_frame :: 
    Ptr PixbufSimpleAnim ->                 -- animation : TInterface (Name {namespace = "GdkPixbuf", name = "PixbufSimpleAnim"})
    Ptr GdkPixbuf.Pixbuf.Pixbuf ->          -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    IO ()

-- | Adds a new frame to /@animation@/. The /@pixbuf@/ must
-- have the dimensions specified when the animation
-- was constructed.
-- 
-- /Since: 2.8/
pixbufSimpleAnimAddFrame ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbufSimpleAnim a, GdkPixbuf.Pixbuf.IsPixbuf b) =>
    a
    -- ^ /@animation@/: a t'GI.GdkPixbuf.Objects.PixbufSimpleAnim.PixbufSimpleAnim'
    -> b
    -- ^ /@pixbuf@/: the pixbuf to add
    -> m ()
pixbufSimpleAnimAddFrame :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPixbufSimpleAnim a, IsPixbuf b) =>
a -> b -> m ()
pixbufSimpleAnimAddFrame a
animation b
pixbuf = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr PixbufSimpleAnim
animation' <- a -> IO (Ptr PixbufSimpleAnim)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
animation
    Ptr Pixbuf
pixbuf' <- b -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
pixbuf
    Ptr PixbufSimpleAnim -> Ptr Pixbuf -> IO ()
gdk_pixbuf_simple_anim_add_frame Ptr PixbufSimpleAnim
animation' Ptr Pixbuf
pixbuf'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
animation
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
pixbuf
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PixbufSimpleAnimAddFrameMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsPixbufSimpleAnim a, GdkPixbuf.Pixbuf.IsPixbuf b) => O.OverloadedMethod PixbufSimpleAnimAddFrameMethodInfo a signature where
    overloadedMethod = pixbufSimpleAnimAddFrame

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


#endif

-- method PixbufSimpleAnim::get_loop
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "animation"
--           , argType =
--               TInterface
--                 Name { namespace = "GdkPixbuf" , name = "PixbufSimpleAnim" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkPixbufSimpleAnim"
--                 , 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_simple_anim_get_loop" gdk_pixbuf_simple_anim_get_loop :: 
    Ptr PixbufSimpleAnim ->                 -- animation : TInterface (Name {namespace = "GdkPixbuf", name = "PixbufSimpleAnim"})
    IO CInt

-- | Gets whether /@animation@/ should loop indefinitely when it reaches the end.
-- 
-- /Since: 2.18/
pixbufSimpleAnimGetLoop ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbufSimpleAnim a) =>
    a
    -- ^ /@animation@/: a t'GI.GdkPixbuf.Objects.PixbufSimpleAnim.PixbufSimpleAnim'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the animation loops forever, 'P.False' otherwise
pixbufSimpleAnimGetLoop :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbufSimpleAnim a) =>
a -> m Bool
pixbufSimpleAnimGetLoop a
animation = 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 PixbufSimpleAnim
animation' <- a -> IO (Ptr PixbufSimpleAnim)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
animation
    CInt
result <- Ptr PixbufSimpleAnim -> IO CInt
gdk_pixbuf_simple_anim_get_loop Ptr PixbufSimpleAnim
animation'
    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
animation
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data PixbufSimpleAnimGetLoopMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPixbufSimpleAnim a) => O.OverloadedMethod PixbufSimpleAnimGetLoopMethodInfo a signature where
    overloadedMethod = pixbufSimpleAnimGetLoop

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


#endif

-- method PixbufSimpleAnim::set_loop
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "animation"
--           , argType =
--               TInterface
--                 Name { namespace = "GdkPixbuf" , name = "PixbufSimpleAnim" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkPixbufSimpleAnim"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "loop"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether to loop the animation"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pixbuf_simple_anim_set_loop" gdk_pixbuf_simple_anim_set_loop :: 
    Ptr PixbufSimpleAnim ->                 -- animation : TInterface (Name {namespace = "GdkPixbuf", name = "PixbufSimpleAnim"})
    CInt ->                                 -- loop : TBasicType TBoolean
    IO ()

-- | Sets whether /@animation@/ should loop indefinitely when it reaches the end.
-- 
-- /Since: 2.18/
pixbufSimpleAnimSetLoop ::
    (B.CallStack.HasCallStack, MonadIO m, IsPixbufSimpleAnim a) =>
    a
    -- ^ /@animation@/: a t'GI.GdkPixbuf.Objects.PixbufSimpleAnim.PixbufSimpleAnim'
    -> Bool
    -- ^ /@loop@/: whether to loop the animation
    -> m ()
pixbufSimpleAnimSetLoop :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbufSimpleAnim a) =>
a -> Bool -> m ()
pixbufSimpleAnimSetLoop a
animation Bool
loop = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr PixbufSimpleAnim
animation' <- a -> IO (Ptr PixbufSimpleAnim)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
animation
    let loop' :: CInt
loop' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
loop
    Ptr PixbufSimpleAnim -> CInt -> IO ()
gdk_pixbuf_simple_anim_set_loop Ptr PixbufSimpleAnim
animation' CInt
loop'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
animation
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PixbufSimpleAnimSetLoopMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsPixbufSimpleAnim a) => O.OverloadedMethod PixbufSimpleAnimSetLoopMethodInfo a signature where
    overloadedMethod = pixbufSimpleAnimSetLoop

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


#endif