{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- An [class/@animationTarget@/] changing the value of a property of a
-- t'GI.GObject.Objects.Object.Object' instance.
-- 
-- /Since: 1.2/

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

module GI.Adw.Objects.PropertyAnimationTarget
    ( 

-- * Exported types
    PropertyAnimationTarget(..)             ,
    IsPropertyAnimationTarget               ,
    toPropertyAnimationTarget               ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [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"), [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"), [getObject]("GI.Adw.Objects.PropertyAnimationTarget#g:method:getObject"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getPspec]("GI.Adw.Objects.PropertyAnimationTarget#g:method:getPspec"), [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)
    ResolvePropertyAnimationTargetMethod    ,
#endif

-- ** getObject #method:getObject#

#if defined(ENABLE_OVERLOADING)
    PropertyAnimationTargetGetObjectMethodInfo,
#endif
    propertyAnimationTargetGetObject        ,


-- ** getPspec #method:getPspec#

#if defined(ENABLE_OVERLOADING)
    PropertyAnimationTargetGetPspecMethodInfo,
#endif
    propertyAnimationTargetGetPspec         ,


-- ** new #method:new#

    propertyAnimationTargetNew              ,


-- ** newForPspec #method:newForPspec#

    propertyAnimationTargetNewForPspec      ,




 -- * Properties


-- ** object #attr:object#
-- | The object whose property will be animated.
-- 
-- The @AdwPropertyAnimationTarget@ instance does not hold a strong reference
-- on the object; make sure the object is kept alive throughout the target\'s
-- lifetime.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    PropertyAnimationTargetObjectPropertyInfo,
#endif
    constructPropertyAnimationTargetObject  ,
    getPropertyAnimationTargetObject        ,
#if defined(ENABLE_OVERLOADING)
    propertyAnimationTargetObject           ,
#endif


-- ** pspec #attr:pspec#
-- | The @GParamSpec@ of the property to be animated.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    PropertyAnimationTargetPspecPropertyInfo,
#endif
    constructPropertyAnimationTargetPspec   ,
    getPropertyAnimationTargetPspec         ,
#if defined(ENABLE_OVERLOADING)
    propertyAnimationTargetPspec            ,
#endif




    ) 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 {-# SOURCE #-} qualified GI.Adw.Objects.AnimationTarget as Adw.AnimationTarget
import qualified GI.GObject.Objects.Object as GObject.Object

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

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

foreign import ccall "adw_property_animation_target_get_type"
    c_adw_property_animation_target_get_type :: IO B.Types.GType

instance B.Types.TypedObject PropertyAnimationTarget where
    glibType :: IO GType
glibType = IO GType
c_adw_property_animation_target_get_type

instance B.Types.GObject PropertyAnimationTarget

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

instance O.HasParentTypes PropertyAnimationTarget
type instance O.ParentTypes PropertyAnimationTarget = '[Adw.AnimationTarget.AnimationTarget, GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolvePropertyAnimationTargetMethod (t :: Symbol) (o :: *) :: * where
    ResolvePropertyAnimationTargetMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolvePropertyAnimationTargetMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolvePropertyAnimationTargetMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolvePropertyAnimationTargetMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolvePropertyAnimationTargetMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolvePropertyAnimationTargetMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolvePropertyAnimationTargetMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolvePropertyAnimationTargetMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolvePropertyAnimationTargetMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolvePropertyAnimationTargetMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolvePropertyAnimationTargetMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolvePropertyAnimationTargetMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolvePropertyAnimationTargetMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolvePropertyAnimationTargetMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolvePropertyAnimationTargetMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolvePropertyAnimationTargetMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolvePropertyAnimationTargetMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolvePropertyAnimationTargetMethod "getObject" o = PropertyAnimationTargetGetObjectMethodInfo
    ResolvePropertyAnimationTargetMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolvePropertyAnimationTargetMethod "getPspec" o = PropertyAnimationTargetGetPspecMethodInfo
    ResolvePropertyAnimationTargetMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolvePropertyAnimationTargetMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolvePropertyAnimationTargetMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolvePropertyAnimationTargetMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolvePropertyAnimationTargetMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- VVV Prop "object"
   -- Type: TInterface (Name {namespace = "GObject", name = "Object"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@object@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' propertyAnimationTarget #object
-- @
getPropertyAnimationTargetObject :: (MonadIO m, IsPropertyAnimationTarget o) => o -> m GObject.Object.Object
getPropertyAnimationTargetObject :: forall (m :: * -> *) o.
(MonadIO m, IsPropertyAnimationTarget o) =>
o -> m Object
getPropertyAnimationTargetObject o
obj = IO Object -> m Object
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Object -> m Object) -> IO Object -> m Object
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Object) -> IO Object
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getPropertyAnimationTargetObject" (IO (Maybe Object) -> IO Object) -> IO (Maybe Object) -> IO Object
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Object -> Object) -> IO (Maybe Object)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"object" ManagedPtr Object -> Object
GObject.Object.Object

-- | Construct a `GValueConstruct` with valid value for the “@object@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPropertyAnimationTargetObject :: (IsPropertyAnimationTarget o, MIO.MonadIO m, GObject.Object.IsObject a) => a -> m (GValueConstruct o)
constructPropertyAnimationTargetObject :: forall o (m :: * -> *) a.
(IsPropertyAnimationTarget o, MonadIO m, IsObject a) =>
a -> m (GValueConstruct o)
constructPropertyAnimationTargetObject 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
"object" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data PropertyAnimationTargetObjectPropertyInfo
instance AttrInfo PropertyAnimationTargetObjectPropertyInfo where
    type AttrAllowedOps PropertyAnimationTargetObjectPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint PropertyAnimationTargetObjectPropertyInfo = IsPropertyAnimationTarget
    type AttrSetTypeConstraint PropertyAnimationTargetObjectPropertyInfo = GObject.Object.IsObject
    type AttrTransferTypeConstraint PropertyAnimationTargetObjectPropertyInfo = GObject.Object.IsObject
    type AttrTransferType PropertyAnimationTargetObjectPropertyInfo = GObject.Object.Object
    type AttrGetType PropertyAnimationTargetObjectPropertyInfo = GObject.Object.Object
    type AttrLabel PropertyAnimationTargetObjectPropertyInfo = "object"
    type AttrOrigin PropertyAnimationTargetObjectPropertyInfo = PropertyAnimationTarget
    attrGet = getPropertyAnimationTargetObject
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo GObject.Object.Object v
    attrConstruct = constructPropertyAnimationTargetObject
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.PropertyAnimationTarget.object"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.3/docs/GI-Adw-Objects-PropertyAnimationTarget.html#g:attr:object"
        })
#endif

-- VVV Prop "pspec"
   -- Type: TParamSpec
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@pspec@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' propertyAnimationTarget #pspec
-- @
getPropertyAnimationTargetPspec :: (MonadIO m, IsPropertyAnimationTarget o) => o -> m GParamSpec
getPropertyAnimationTargetPspec :: forall (m :: * -> *) o.
(MonadIO m, IsPropertyAnimationTarget o) =>
o -> m GParamSpec
getPropertyAnimationTargetPspec o
obj = IO GParamSpec -> m GParamSpec
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe GParamSpec) -> IO GParamSpec
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getPropertyAnimationTargetPspec" (IO (Maybe GParamSpec) -> IO GParamSpec)
-> IO (Maybe GParamSpec) -> IO GParamSpec
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe GParamSpec)
forall a. GObject a => a -> String -> IO (Maybe GParamSpec)
B.Properties.getObjectPropertyParamSpec o
obj String
"pspec"

-- | Construct a `GValueConstruct` with valid value for the “@pspec@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPropertyAnimationTargetPspec :: (IsPropertyAnimationTarget o, MIO.MonadIO m) => GParamSpec -> m (GValueConstruct o)
constructPropertyAnimationTargetPspec :: forall o (m :: * -> *).
(IsPropertyAnimationTarget o, MonadIO m) =>
GParamSpec -> m (GValueConstruct o)
constructPropertyAnimationTargetPspec GParamSpec
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 GParamSpec -> IO (GValueConstruct o)
forall o. String -> Maybe GParamSpec -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyParamSpec String
"pspec" (GParamSpec -> Maybe GParamSpec
forall a. a -> Maybe a
P.Just GParamSpec
val)

#if defined(ENABLE_OVERLOADING)
data PropertyAnimationTargetPspecPropertyInfo
instance AttrInfo PropertyAnimationTargetPspecPropertyInfo where
    type AttrAllowedOps PropertyAnimationTargetPspecPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint PropertyAnimationTargetPspecPropertyInfo = IsPropertyAnimationTarget
    type AttrSetTypeConstraint PropertyAnimationTargetPspecPropertyInfo = (~) GParamSpec
    type AttrTransferTypeConstraint PropertyAnimationTargetPspecPropertyInfo = (~) GParamSpec
    type AttrTransferType PropertyAnimationTargetPspecPropertyInfo = GParamSpec
    type AttrGetType PropertyAnimationTargetPspecPropertyInfo = GParamSpec
    type AttrLabel PropertyAnimationTargetPspecPropertyInfo = "pspec"
    type AttrOrigin PropertyAnimationTargetPspecPropertyInfo = PropertyAnimationTarget
    attrGet = getPropertyAnimationTargetPspec
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructPropertyAnimationTargetPspec
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.PropertyAnimationTarget.pspec"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.3/docs/GI-Adw-Objects-PropertyAnimationTarget.html#g:attr:pspec"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList PropertyAnimationTarget
type instance O.AttributeList PropertyAnimationTarget = PropertyAnimationTargetAttributeList
type PropertyAnimationTargetAttributeList = ('[ '("object", PropertyAnimationTargetObjectPropertyInfo), '("pspec", PropertyAnimationTargetPspecPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
propertyAnimationTargetObject :: AttrLabelProxy "object"
propertyAnimationTargetObject = AttrLabelProxy

propertyAnimationTargetPspec :: AttrLabelProxy "pspec"
propertyAnimationTargetPspec = AttrLabelProxy

#endif

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

#endif

-- method PropertyAnimationTarget::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "object"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an object to be animated"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the name of the property on @object to animate"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Adw" , name = "PropertyAnimationTarget" })
-- throws : False
-- Skip return : False

foreign import ccall "adw_property_animation_target_new" adw_property_animation_target_new :: 
    Ptr GObject.Object.Object ->            -- object : TInterface (Name {namespace = "GObject", name = "Object"})
    CString ->                              -- property_name : TBasicType TUTF8
    IO (Ptr PropertyAnimationTarget)

-- | Creates a new @AdwPropertyAnimationTarget@ for the /@propertyName@/ property on
-- /@object@/.
-- 
-- /Since: 1.2/
propertyAnimationTargetNew ::
    (B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a) =>
    a
    -- ^ /@object@/: an object to be animated
    -> T.Text
    -- ^ /@propertyName@/: the name of the property on /@object@/ to animate
    -> m PropertyAnimationTarget
    -- ^ __Returns:__ the newly created @AdwPropertyAnimationTarget@
propertyAnimationTargetNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
a -> Text -> m PropertyAnimationTarget
propertyAnimationTargetNew a
object Text
propertyName = IO PropertyAnimationTarget -> m PropertyAnimationTarget
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PropertyAnimationTarget -> m PropertyAnimationTarget)
-> IO PropertyAnimationTarget -> m PropertyAnimationTarget
forall a b. (a -> b) -> a -> b
$ do
    Ptr Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
    CString
propertyName' <- Text -> IO CString
textToCString Text
propertyName
    Ptr PropertyAnimationTarget
result <- Ptr Object -> CString -> IO (Ptr PropertyAnimationTarget)
adw_property_animation_target_new Ptr Object
object' CString
propertyName'
    Text -> Ptr PropertyAnimationTarget -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"propertyAnimationTargetNew" Ptr PropertyAnimationTarget
result
    PropertyAnimationTarget
result' <- ((ManagedPtr PropertyAnimationTarget -> PropertyAnimationTarget)
-> Ptr PropertyAnimationTarget -> IO PropertyAnimationTarget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr PropertyAnimationTarget -> PropertyAnimationTarget
PropertyAnimationTarget) Ptr PropertyAnimationTarget
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
propertyName'
    PropertyAnimationTarget -> IO PropertyAnimationTarget
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PropertyAnimationTarget
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method PropertyAnimationTarget::new_for_pspec
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "object"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an object to be animated"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pspec"
--           , argType = TParamSpec
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the param spec of the property on @object to animate"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Adw" , name = "PropertyAnimationTarget" })
-- throws : False
-- Skip return : False

foreign import ccall "adw_property_animation_target_new_for_pspec" adw_property_animation_target_new_for_pspec :: 
    Ptr GObject.Object.Object ->            -- object : TInterface (Name {namespace = "GObject", name = "Object"})
    Ptr GParamSpec ->                       -- pspec : TParamSpec
    IO (Ptr PropertyAnimationTarget)

-- | Creates a new @AdwPropertyAnimationTarget@ for the /@pspec@/ property on
-- /@object@/.
-- 
-- /Since: 1.2/
propertyAnimationTargetNewForPspec ::
    (B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a) =>
    a
    -- ^ /@object@/: an object to be animated
    -> GParamSpec
    -- ^ /@pspec@/: the param spec of the property on /@object@/ to animate
    -> m PropertyAnimationTarget
    -- ^ __Returns:__ new newly created @AdwPropertyAnimationTarget@
propertyAnimationTargetNewForPspec :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
a -> GParamSpec -> m PropertyAnimationTarget
propertyAnimationTargetNewForPspec a
object GParamSpec
pspec = IO PropertyAnimationTarget -> m PropertyAnimationTarget
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PropertyAnimationTarget -> m PropertyAnimationTarget)
-> IO PropertyAnimationTarget -> m PropertyAnimationTarget
forall a b. (a -> b) -> a -> b
$ do
    Ptr Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
    Ptr GParamSpec
pspec' <- GParamSpec -> IO (Ptr GParamSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GParamSpec
pspec
    Ptr PropertyAnimationTarget
result <- Ptr Object -> Ptr GParamSpec -> IO (Ptr PropertyAnimationTarget)
adw_property_animation_target_new_for_pspec Ptr Object
object' Ptr GParamSpec
pspec'
    Text -> Ptr PropertyAnimationTarget -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"propertyAnimationTargetNewForPspec" Ptr PropertyAnimationTarget
result
    PropertyAnimationTarget
result' <- ((ManagedPtr PropertyAnimationTarget -> PropertyAnimationTarget)
-> Ptr PropertyAnimationTarget -> IO PropertyAnimationTarget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr PropertyAnimationTarget -> PropertyAnimationTarget
PropertyAnimationTarget) Ptr PropertyAnimationTarget
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
    GParamSpec -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GParamSpec
pspec
    PropertyAnimationTarget -> IO PropertyAnimationTarget
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PropertyAnimationTarget
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method PropertyAnimationTarget::get_object
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Adw" , name = "PropertyAnimationTarget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a property animation target"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GObject" , name = "Object" })
-- throws : False
-- Skip return : False

foreign import ccall "adw_property_animation_target_get_object" adw_property_animation_target_get_object :: 
    Ptr PropertyAnimationTarget ->          -- self : TInterface (Name {namespace = "Adw", name = "PropertyAnimationTarget"})
    IO (Ptr GObject.Object.Object)

-- | Gets the object animated by /@self@/.
-- 
-- The @AdwPropertyAnimationTarget@ instance does not hold a strong reference on
-- the object; make sure the object is kept alive throughout the target\'s
-- lifetime.
-- 
-- /Since: 1.2/
propertyAnimationTargetGetObject ::
    (B.CallStack.HasCallStack, MonadIO m, IsPropertyAnimationTarget a) =>
    a
    -- ^ /@self@/: a property animation target
    -> m GObject.Object.Object
    -- ^ __Returns:__ the animated object
propertyAnimationTargetGetObject :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPropertyAnimationTarget a) =>
a -> m Object
propertyAnimationTargetGetObject a
self = IO Object -> m Object
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Object -> m Object) -> IO Object -> m Object
forall a b. (a -> b) -> a -> b
$ do
    Ptr PropertyAnimationTarget
self' <- a -> IO (Ptr PropertyAnimationTarget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Object
result <- Ptr PropertyAnimationTarget -> IO (Ptr Object)
adw_property_animation_target_get_object Ptr PropertyAnimationTarget
self'
    Text -> Ptr Object -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"propertyAnimationTargetGetObject" Ptr Object
result
    Object
result' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
GObject.Object.Object) Ptr Object
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Object -> IO Object
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Object
result'

#if defined(ENABLE_OVERLOADING)
data PropertyAnimationTargetGetObjectMethodInfo
instance (signature ~ (m GObject.Object.Object), MonadIO m, IsPropertyAnimationTarget a) => O.OverloadedMethod PropertyAnimationTargetGetObjectMethodInfo a signature where
    overloadedMethod = propertyAnimationTargetGetObject

instance O.OverloadedMethodInfo PropertyAnimationTargetGetObjectMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.PropertyAnimationTarget.propertyAnimationTargetGetObject",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.3/docs/GI-Adw-Objects-PropertyAnimationTarget.html#v:propertyAnimationTargetGetObject"
        })


#endif

-- method PropertyAnimationTarget::get_pspec
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Adw" , name = "PropertyAnimationTarget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a property animation target"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TParamSpec
-- throws : False
-- Skip return : False

foreign import ccall "adw_property_animation_target_get_pspec" adw_property_animation_target_get_pspec :: 
    Ptr PropertyAnimationTarget ->          -- self : TInterface (Name {namespace = "Adw", name = "PropertyAnimationTarget"})
    IO (Ptr GParamSpec)

-- | Gets the @GParamSpec@ of the property animated by /@self@/.
-- 
-- /Since: 1.2/
propertyAnimationTargetGetPspec ::
    (B.CallStack.HasCallStack, MonadIO m, IsPropertyAnimationTarget a) =>
    a
    -- ^ /@self@/: a property animation target
    -> m GParamSpec
    -- ^ __Returns:__ the animated property\'s @GParamSpec@
propertyAnimationTargetGetPspec :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPropertyAnimationTarget a) =>
a -> m GParamSpec
propertyAnimationTargetGetPspec a
self = IO GParamSpec -> m GParamSpec
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec
forall a b. (a -> b) -> a -> b
$ do
    Ptr PropertyAnimationTarget
self' <- a -> IO (Ptr PropertyAnimationTarget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr GParamSpec
result <- Ptr PropertyAnimationTarget -> IO (Ptr GParamSpec)
adw_property_animation_target_get_pspec Ptr PropertyAnimationTarget
self'
    Text -> Ptr GParamSpec -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"propertyAnimationTargetGetPspec" Ptr GParamSpec
result
    GParamSpec
result' <- Ptr GParamSpec -> IO GParamSpec
B.GParamSpec.newGParamSpecFromPtr Ptr GParamSpec
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    GParamSpec -> IO GParamSpec
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GParamSpec
result'

#if defined(ENABLE_OVERLOADING)
data PropertyAnimationTargetGetPspecMethodInfo
instance (signature ~ (m GParamSpec), MonadIO m, IsPropertyAnimationTarget a) => O.OverloadedMethod PropertyAnimationTargetGetPspecMethodInfo a signature where
    overloadedMethod = propertyAnimationTargetGetPspec

instance O.OverloadedMethodInfo PropertyAnimationTargetGetPspecMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.PropertyAnimationTarget.propertyAnimationTargetGetPspec",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.3/docs/GI-Adw-Objects-PropertyAnimationTarget.html#v:propertyAnimationTargetGetPspec"
        })


#endif