{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Dazzle.Objects.Animation
(
Animation(..) ,
IsAnimation ,
toAnimation ,
#if defined(ENABLE_OVERLOADING)
ResolveAnimationMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
AnimationAddPropertyMethodInfo ,
#endif
animationAddProperty ,
animationCalculateDuration ,
#if defined(ENABLE_OVERLOADING)
AnimationStartMethodInfo ,
#endif
animationStart ,
#if defined(ENABLE_OVERLOADING)
AnimationStopMethodInfo ,
#endif
animationStop ,
#if defined(ENABLE_OVERLOADING)
AnimationDurationPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
animationDuration ,
#endif
constructAnimationDuration ,
#if defined(ENABLE_OVERLOADING)
AnimationFrameClockPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
animationFrameClock ,
#endif
constructAnimationFrameClock ,
#if defined(ENABLE_OVERLOADING)
AnimationModePropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
animationMode ,
#endif
constructAnimationMode ,
#if defined(ENABLE_OVERLOADING)
AnimationTargetPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
animationTarget ,
#endif
constructAnimationTarget ,
AnimationTickCallback ,
#if defined(ENABLE_OVERLOADING)
AnimationTickSignalInfo ,
#endif
afterAnimationTick ,
onAnimationTick ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import {-# SOURCE #-} qualified GI.Dazzle.Enums as Dazzle.Enums
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Objects.FrameClock as Gdk.FrameClock
import qualified GI.Gdk.Objects.Monitor as Gdk.Monitor
#else
import {-# SOURCE #-} qualified GI.Dazzle.Enums as Dazzle.Enums
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Objects.FrameClock as Gdk.FrameClock
import qualified GI.Gdk.Objects.Monitor as Gdk.Monitor
#endif
newtype Animation = Animation (SP.ManagedPtr Animation)
deriving (Animation -> Animation -> Bool
(Animation -> Animation -> Bool)
-> (Animation -> Animation -> Bool) -> Eq Animation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Animation -> Animation -> Bool
== :: Animation -> Animation -> Bool
$c/= :: Animation -> Animation -> Bool
/= :: Animation -> Animation -> Bool
Eq)
instance SP.ManagedPtrNewtype Animation where
toManagedPtr :: Animation -> ManagedPtr Animation
toManagedPtr (Animation ManagedPtr Animation
p) = ManagedPtr Animation
p
foreign import ccall "dzl_animation_get_type"
c_dzl_animation_get_type :: IO B.Types.GType
instance B.Types.TypedObject Animation where
glibType :: IO GType
glibType = IO GType
c_dzl_animation_get_type
instance B.Types.GObject Animation
class (SP.GObject o, O.IsDescendantOf Animation o) => IsAnimation o
instance (SP.GObject o, O.IsDescendantOf Animation o) => IsAnimation o
instance O.HasParentTypes Animation
type instance O.ParentTypes Animation = '[GObject.Object.Object]
toAnimation :: (MIO.MonadIO m, IsAnimation o) => o -> m Animation
toAnimation :: forall (m :: * -> *) o.
(MonadIO m, IsAnimation o) =>
o -> m Animation
toAnimation = IO Animation -> m Animation
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Animation -> m Animation)
-> (o -> IO Animation) -> o -> m Animation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Animation -> Animation) -> o -> IO Animation
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Animation -> Animation
Animation
instance B.GValue.IsGValue (Maybe Animation) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_dzl_animation_get_type
gvalueSet_ :: Ptr GValue -> Maybe Animation -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Animation
P.Nothing = Ptr GValue -> Ptr Animation -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Animation
forall a. Ptr a
FP.nullPtr :: FP.Ptr Animation)
gvalueSet_ Ptr GValue
gv (P.Just Animation
obj) = Animation -> (Ptr Animation -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Animation
obj (Ptr GValue -> Ptr Animation -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe Animation)
gvalueGet_ Ptr GValue
gv = do
Ptr Animation
ptr <- Ptr GValue -> IO (Ptr Animation)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Animation)
if Ptr Animation
ptr Ptr Animation -> Ptr Animation -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Animation
forall a. Ptr a
FP.nullPtr
then Animation -> Maybe Animation
forall a. a -> Maybe a
P.Just (Animation -> Maybe Animation)
-> IO Animation -> IO (Maybe Animation)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Animation -> Animation)
-> Ptr Animation -> IO Animation
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Animation -> Animation
Animation Ptr Animation
ptr
else Maybe Animation -> IO (Maybe Animation)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Animation
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveAnimationMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveAnimationMethod "addProperty" o = AnimationAddPropertyMethodInfo
ResolveAnimationMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveAnimationMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveAnimationMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveAnimationMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveAnimationMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveAnimationMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveAnimationMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveAnimationMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveAnimationMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveAnimationMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveAnimationMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveAnimationMethod "start" o = AnimationStartMethodInfo
ResolveAnimationMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveAnimationMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveAnimationMethod "stop" o = AnimationStopMethodInfo
ResolveAnimationMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveAnimationMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveAnimationMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveAnimationMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveAnimationMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveAnimationMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveAnimationMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveAnimationMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveAnimationMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveAnimationMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveAnimationMethod t Animation, O.OverloadedMethod info Animation p) => OL.IsLabel t (Animation -> 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 ~ ResolveAnimationMethod t Animation, O.OverloadedMethod info Animation p, R.HasField t Animation p) => R.HasField t Animation p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveAnimationMethod t Animation, O.OverloadedMethodInfo info Animation) => OL.IsLabel t (O.MethodProxy info Animation) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
type AnimationTickCallback =
IO ()
type C_AnimationTickCallback =
Ptr Animation ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_AnimationTickCallback :: C_AnimationTickCallback -> IO (FunPtr C_AnimationTickCallback)
wrap_AnimationTickCallback ::
GObject a => (a -> AnimationTickCallback) ->
C_AnimationTickCallback
wrap_AnimationTickCallback :: forall a. GObject a => (a -> IO ()) -> C_AnimationTickCallback
wrap_AnimationTickCallback a -> IO ()
gi'cb Ptr Animation
gi'selfPtr Ptr ()
_ = do
Ptr Animation -> (Animation -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr Animation
gi'selfPtr ((Animation -> IO ()) -> IO ()) -> (Animation -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Animation
gi'self -> a -> IO ()
gi'cb (Animation -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Animation
gi'self)
onAnimationTick :: (IsAnimation a, MonadIO m) => a -> ((?self :: a) => AnimationTickCallback) -> m SignalHandlerId
onAnimationTick :: forall a (m :: * -> *).
(IsAnimation a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onAnimationTick a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_AnimationTickCallback
wrapped' = (a -> IO ()) -> C_AnimationTickCallback
forall a. GObject a => (a -> IO ()) -> C_AnimationTickCallback
wrap_AnimationTickCallback a -> IO ()
wrapped
FunPtr C_AnimationTickCallback
wrapped'' <- C_AnimationTickCallback -> IO (FunPtr C_AnimationTickCallback)
mk_AnimationTickCallback C_AnimationTickCallback
wrapped'
a
-> Text
-> FunPtr C_AnimationTickCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"tick" FunPtr C_AnimationTickCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterAnimationTick :: (IsAnimation a, MonadIO m) => a -> ((?self :: a) => AnimationTickCallback) -> m SignalHandlerId
afterAnimationTick :: forall a (m :: * -> *).
(IsAnimation a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterAnimationTick a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_AnimationTickCallback
wrapped' = (a -> IO ()) -> C_AnimationTickCallback
forall a. GObject a => (a -> IO ()) -> C_AnimationTickCallback
wrap_AnimationTickCallback a -> IO ()
wrapped
FunPtr C_AnimationTickCallback
wrapped'' <- C_AnimationTickCallback -> IO (FunPtr C_AnimationTickCallback)
mk_AnimationTickCallback C_AnimationTickCallback
wrapped'
a
-> Text
-> FunPtr C_AnimationTickCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"tick" FunPtr C_AnimationTickCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data AnimationTickSignalInfo
instance SignalInfo AnimationTickSignalInfo where
type HaskellCallbackType AnimationTickSignalInfo = AnimationTickCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_AnimationTickCallback cb
cb'' <- mk_AnimationTickCallback cb'
connectSignalFunPtr obj "tick" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Animation::tick"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-Animation.html#g:signal:tick"})
#endif
constructAnimationDuration :: (IsAnimation o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructAnimationDuration :: forall o (m :: * -> *).
(IsAnimation o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructAnimationDuration Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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 -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"duration" Word32
val
#if defined(ENABLE_OVERLOADING)
data AnimationDurationPropertyInfo
instance AttrInfo AnimationDurationPropertyInfo where
type AttrAllowedOps AnimationDurationPropertyInfo = '[ 'AttrConstruct]
type AttrBaseTypeConstraint AnimationDurationPropertyInfo = IsAnimation
type AttrSetTypeConstraint AnimationDurationPropertyInfo = (~) Word32
type AttrTransferTypeConstraint AnimationDurationPropertyInfo = (~) Word32
type AttrTransferType AnimationDurationPropertyInfo = Word32
type AttrGetType AnimationDurationPropertyInfo = ()
type AttrLabel AnimationDurationPropertyInfo = "duration"
type AttrOrigin AnimationDurationPropertyInfo = Animation
attrGet = undefined
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructAnimationDuration
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Animation.duration"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-Animation.html#g:attr:duration"
})
#endif
constructAnimationFrameClock :: (IsAnimation o, MIO.MonadIO m, Gdk.FrameClock.IsFrameClock a) => a -> m (GValueConstruct o)
constructAnimationFrameClock :: forall o (m :: * -> *) a.
(IsAnimation o, MonadIO m, IsFrameClock a) =>
a -> m (GValueConstruct o)
constructAnimationFrameClock a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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 -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"frame-clock" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data AnimationFrameClockPropertyInfo
instance AttrInfo AnimationFrameClockPropertyInfo where
type AttrAllowedOps AnimationFrameClockPropertyInfo = '[ 'AttrConstruct, 'AttrClear]
type AttrBaseTypeConstraint AnimationFrameClockPropertyInfo = IsAnimation
type AttrSetTypeConstraint AnimationFrameClockPropertyInfo = Gdk.FrameClock.IsFrameClock
type AttrTransferTypeConstraint AnimationFrameClockPropertyInfo = Gdk.FrameClock.IsFrameClock
type AttrTransferType AnimationFrameClockPropertyInfo = Gdk.FrameClock.FrameClock
type AttrGetType AnimationFrameClockPropertyInfo = ()
type AttrLabel AnimationFrameClockPropertyInfo = "frame-clock"
type AttrOrigin AnimationFrameClockPropertyInfo = Animation
attrGet = undefined
attrSet = undefined
attrTransfer _ v = do
unsafeCastTo Gdk.FrameClock.FrameClock v
attrConstruct = constructAnimationFrameClock
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Animation.frameClock"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-Animation.html#g:attr:frameClock"
})
#endif
constructAnimationMode :: (IsAnimation o, MIO.MonadIO m) => Dazzle.Enums.AnimationMode -> m (GValueConstruct o)
constructAnimationMode :: forall o (m :: * -> *).
(IsAnimation o, MonadIO m) =>
AnimationMode -> m (GValueConstruct o)
constructAnimationMode AnimationMode
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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 -> AnimationMode -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"mode" AnimationMode
val
#if defined(ENABLE_OVERLOADING)
data AnimationModePropertyInfo
instance AttrInfo AnimationModePropertyInfo where
type AttrAllowedOps AnimationModePropertyInfo = '[ 'AttrConstruct]
type AttrBaseTypeConstraint AnimationModePropertyInfo = IsAnimation
type AttrSetTypeConstraint AnimationModePropertyInfo = (~) Dazzle.Enums.AnimationMode
type AttrTransferTypeConstraint AnimationModePropertyInfo = (~) Dazzle.Enums.AnimationMode
type AttrTransferType AnimationModePropertyInfo = Dazzle.Enums.AnimationMode
type AttrGetType AnimationModePropertyInfo = ()
type AttrLabel AnimationModePropertyInfo = "mode"
type AttrOrigin AnimationModePropertyInfo = Animation
attrGet = undefined
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructAnimationMode
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Animation.mode"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-Animation.html#g:attr:mode"
})
#endif
constructAnimationTarget :: (IsAnimation o, MIO.MonadIO m, GObject.Object.IsObject a) => a -> m (GValueConstruct o)
constructAnimationTarget :: forall o (m :: * -> *) a.
(IsAnimation o, MonadIO m, IsObject a) =>
a -> m (GValueConstruct o)
constructAnimationTarget a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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 -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"target" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data AnimationTargetPropertyInfo
instance AttrInfo AnimationTargetPropertyInfo where
type AttrAllowedOps AnimationTargetPropertyInfo = '[ 'AttrConstruct, 'AttrClear]
type AttrBaseTypeConstraint AnimationTargetPropertyInfo = IsAnimation
type AttrSetTypeConstraint AnimationTargetPropertyInfo = GObject.Object.IsObject
type AttrTransferTypeConstraint AnimationTargetPropertyInfo = GObject.Object.IsObject
type AttrTransferType AnimationTargetPropertyInfo = GObject.Object.Object
type AttrGetType AnimationTargetPropertyInfo = ()
type AttrLabel AnimationTargetPropertyInfo = "target"
type AttrOrigin AnimationTargetPropertyInfo = Animation
attrGet = undefined
attrSet = undefined
attrTransfer _ v = do
unsafeCastTo GObject.Object.Object v
attrConstruct = constructAnimationTarget
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Animation.target"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-Animation.html#g:attr:target"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Animation
type instance O.AttributeList Animation = AnimationAttributeList
type AnimationAttributeList = ('[ '("duration", AnimationDurationPropertyInfo), '("frameClock", AnimationFrameClockPropertyInfo), '("mode", AnimationModePropertyInfo), '("target", AnimationTargetPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
animationDuration :: AttrLabelProxy "duration"
animationDuration = AttrLabelProxy
animationFrameClock :: AttrLabelProxy "frameClock"
animationFrameClock = AttrLabelProxy
animationMode :: AttrLabelProxy "mode"
animationMode = AttrLabelProxy
animationTarget :: AttrLabelProxy "target"
animationTarget = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Animation = AnimationSignalList
type AnimationSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo), '("tick", AnimationTickSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "dzl_animation_add_property" dzl_animation_add_property ::
Ptr Animation ->
Ptr GParamSpec ->
Ptr GValue ->
IO ()
animationAddProperty ::
(B.CallStack.HasCallStack, MonadIO m, IsAnimation a) =>
a
-> GParamSpec
-> GValue
-> m ()
animationAddProperty :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAnimation a) =>
a -> GParamSpec -> GValue -> m ()
animationAddProperty a
animation GParamSpec
pspec GValue
value = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Animation
animation' <- a -> IO (Ptr Animation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
animation
Ptr GParamSpec
pspec' <- GParamSpec -> IO (Ptr GParamSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GParamSpec
pspec
Ptr GValue
value' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
value
Ptr Animation -> Ptr GParamSpec -> Ptr GValue -> IO ()
dzl_animation_add_property Ptr Animation
animation' Ptr GParamSpec
pspec' Ptr GValue
value'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
animation
GParamSpec -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GParamSpec
pspec
GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
value
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AnimationAddPropertyMethodInfo
instance (signature ~ (GParamSpec -> GValue -> m ()), MonadIO m, IsAnimation a) => O.OverloadedMethod AnimationAddPropertyMethodInfo a signature where
overloadedMethod = animationAddProperty
instance O.OverloadedMethodInfo AnimationAddPropertyMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Animation.animationAddProperty",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-Animation.html#v:animationAddProperty"
})
#endif
foreign import ccall "dzl_animation_start" dzl_animation_start ::
Ptr Animation ->
IO ()
animationStart ::
(B.CallStack.HasCallStack, MonadIO m, IsAnimation a) =>
a
-> m ()
animationStart :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAnimation a) =>
a -> m ()
animationStart a
animation = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Animation
animation' <- a -> IO (Ptr Animation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
animation
Ptr Animation -> IO ()
dzl_animation_start Ptr Animation
animation'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
animation
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AnimationStartMethodInfo
instance (signature ~ (m ()), MonadIO m, IsAnimation a) => O.OverloadedMethod AnimationStartMethodInfo a signature where
overloadedMethod = animationStart
instance O.OverloadedMethodInfo AnimationStartMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Animation.animationStart",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-Animation.html#v:animationStart"
})
#endif
foreign import ccall "dzl_animation_stop" dzl_animation_stop ::
Ptr Animation ->
IO ()
animationStop ::
(B.CallStack.HasCallStack, MonadIO m, IsAnimation a) =>
Maybe (a)
-> m ()
animationStop :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAnimation a) =>
Maybe a -> m ()
animationStop Maybe a
animation = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Animation
maybeAnimation <- case Maybe a
animation of
Maybe a
Nothing -> Ptr Animation -> IO (Ptr Animation)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Animation
forall a. Ptr a
nullPtr
Just a
jAnimation -> do
Ptr Animation
jAnimation' <- a -> IO (Ptr Animation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jAnimation
Ptr Animation -> IO (Ptr Animation)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Animation
jAnimation'
Ptr Animation -> IO ()
dzl_animation_stop Ptr Animation
maybeAnimation
Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
animation a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AnimationStopMethodInfo
instance (signature ~ (m ()), MonadIO m, IsAnimation a) => O.OverloadedMethod AnimationStopMethodInfo a signature where
overloadedMethod i = animationStop (Just i)
instance O.OverloadedMethodInfo AnimationStopMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Animation.animationStop",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-Animation.html#v:animationStop"
})
#endif
foreign import ccall "dzl_animation_calculate_duration" dzl_animation_calculate_duration ::
Ptr Gdk.Monitor.Monitor ->
CDouble ->
CDouble ->
IO Word32
animationCalculateDuration ::
(B.CallStack.HasCallStack, MonadIO m, Gdk.Monitor.IsMonitor a) =>
a
-> Double
-> Double
-> m Word32
animationCalculateDuration :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMonitor a) =>
a -> Double -> Double -> m Word32
animationCalculateDuration a
monitor Double
fromValue Double
toValue = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
Ptr Monitor
monitor' <- a -> IO (Ptr Monitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
monitor
let fromValue' :: CDouble
fromValue' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
fromValue
let toValue' :: CDouble
toValue' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
toValue
Word32
result <- Ptr Monitor -> CDouble -> CDouble -> IO Word32
dzl_animation_calculate_duration Ptr Monitor
monitor' CDouble
fromValue' CDouble
toValue'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
monitor
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
#endif