{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GdkPixbuf.Objects.PixbufSimpleAnim
(
PixbufSimpleAnim(..) ,
IsPixbufSimpleAnim ,
toPixbufSimpleAnim ,
#if defined(ENABLE_OVERLOADING)
ResolvePixbufSimpleAnimMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
PixbufSimpleAnimAddFrameMethodInfo ,
#endif
pixbufSimpleAnimAddFrame ,
#if defined(ENABLE_OVERLOADING)
PixbufSimpleAnimGetLoopMethodInfo ,
#endif
pixbufSimpleAnimGetLoop ,
pixbufSimpleAnimNew ,
#if defined(ENABLE_OVERLOADING)
PixbufSimpleAnimSetLoopMethodInfo ,
#endif
pixbufSimpleAnimSetLoop ,
#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.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.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.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
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
instance B.GValue.IsGValue PixbufSimpleAnim where
toGValue :: PixbufSimpleAnim -> IO GValue
toGValue PixbufSimpleAnim
o = do
GType
gtype <- IO GType
c_gdk_pixbuf_simple_anim_get_type
PixbufSimpleAnim
-> (Ptr PixbufSimpleAnim -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr PixbufSimpleAnim
o (GType
-> (GValue -> Ptr PixbufSimpleAnim -> IO ())
-> Ptr PixbufSimpleAnim
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr PixbufSimpleAnim -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO PixbufSimpleAnim
fromGValue GValue
gv = do
Ptr PixbufSimpleAnim
ptr <- GValue -> IO (Ptr PixbufSimpleAnim)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr PixbufSimpleAnim)
(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
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]
toPixbufSimpleAnim :: (MonadIO m, IsPixbufSimpleAnim o) => o -> m PixbufSimpleAnim
toPixbufSimpleAnim :: o -> m PixbufSimpleAnim
toPixbufSimpleAnim = IO PixbufSimpleAnim -> m PixbufSimpleAnim
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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'
unsafeCastTo ManagedPtr PixbufSimpleAnim -> PixbufSimpleAnim
PixbufSimpleAnim
#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.MethodInfo 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
#endif
getPixbufSimpleAnimLoop :: (MonadIO m, IsPixbufSimpleAnim o) => o -> m Bool
getPixbufSimpleAnimLoop :: o -> m Bool
getPixbufSimpleAnimLoop o
obj = 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
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"loop"
setPixbufSimpleAnimLoop :: (MonadIO m, IsPixbufSimpleAnim o) => o -> Bool -> m ()
setPixbufSimpleAnimLoop :: o -> Bool -> m ()
setPixbufSimpleAnimLoop o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"loop" Bool
val
constructPixbufSimpleAnimLoop :: (IsPixbufSimpleAnim o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructPixbufSimpleAnimLoop :: 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
$ 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
#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
foreign import ccall "gdk_pixbuf_simple_anim_new" gdk_pixbuf_simple_anim_new ::
Int32 ->
Int32 ->
CFloat ->
IO (Ptr PixbufSimpleAnim)
pixbufSimpleAnimNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
Int32
-> Int32
-> Float
-> m PixbufSimpleAnim
pixbufSimpleAnimNew :: 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
foreign import ccall "gdk_pixbuf_simple_anim_add_frame" gdk_pixbuf_simple_anim_add_frame ::
Ptr PixbufSimpleAnim ->
Ptr GdkPixbuf.Pixbuf.Pixbuf ->
IO ()
pixbufSimpleAnimAddFrame ::
(B.CallStack.HasCallStack, MonadIO m, IsPixbufSimpleAnim a, GdkPixbuf.Pixbuf.IsPixbuf b) =>
a
-> b
-> m ()
pixbufSimpleAnimAddFrame :: 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.MethodInfo PixbufSimpleAnimAddFrameMethodInfo a signature where
overloadedMethod = pixbufSimpleAnimAddFrame
#endif
foreign import ccall "gdk_pixbuf_simple_anim_get_loop" gdk_pixbuf_simple_anim_get_loop ::
Ptr PixbufSimpleAnim ->
IO CInt
pixbufSimpleAnimGetLoop ::
(B.CallStack.HasCallStack, MonadIO m, IsPixbufSimpleAnim a) =>
a
-> m Bool
pixbufSimpleAnimGetLoop :: 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.MethodInfo PixbufSimpleAnimGetLoopMethodInfo a signature where
overloadedMethod = pixbufSimpleAnimGetLoop
#endif
foreign import ccall "gdk_pixbuf_simple_anim_set_loop" gdk_pixbuf_simple_anim_set_loop ::
Ptr PixbufSimpleAnim ->
CInt ->
IO ()
pixbufSimpleAnimSetLoop ::
(B.CallStack.HasCallStack, MonadIO m, IsPixbufSimpleAnim a) =>
a
-> Bool
-> m ()
pixbufSimpleAnimSetLoop :: 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.MethodInfo PixbufSimpleAnimSetLoopMethodInfo a signature where
overloadedMethod = pixbufSimpleAnimSetLoop
#endif