{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.GObject.Objects.Binding.Binding' is the representation of a binding between a property on a
-- t'GI.GObject.Objects.Object.Object' instance (or source) and another property on another t'GI.GObject.Objects.Object.Object'
-- instance (or target). Whenever the source property changes, the same
-- value is applied to the target property; for instance, the following
-- binding:
-- 
-- 
-- === /C code/
-- >
-- >  g_object_bind_property (object1, "property-a",
-- >                          object2, "property-b",
-- >                          G_BINDING_DEFAULT);
-- 
-- 
-- will cause the property named \"property-b\" of /@object2@/ to be updated
-- every time @/g_object_set()/@ or the specific accessor changes the value of
-- the property \"property-a\" of /@object1@/.
-- 
-- It is possible to create a bidirectional binding between two properties
-- of two t'GI.GObject.Objects.Object.Object' instances, so that if either property changes, the
-- other is updated as well, for instance:
-- 
-- 
-- === /C code/
-- >
-- >  g_object_bind_property (object1, "property-a",
-- >                          object2, "property-b",
-- >                          G_BINDING_BIDIRECTIONAL);
-- 
-- 
-- will keep the two properties in sync.
-- 
-- It is also possible to set a custom transformation function (in both
-- directions, in case of a bidirectional binding) to apply a custom
-- transformation from the source value to the target value before
-- applying it; for instance, the following binding:
-- 
-- 
-- === /C code/
-- >
-- >  g_object_bind_property_full (adjustment1, "value",
-- >                               adjustment2, "value",
-- >                               G_BINDING_BIDIRECTIONAL,
-- >                               celsius_to_fahrenheit,
-- >                               fahrenheit_to_celsius,
-- >                               NULL, NULL);
-- 
-- 
-- will keep the \"value\" property of the two adjustments in sync; the
-- /@celsiusToFahrenheit@/ function will be called whenever the \"value\"
-- property of /@adjustment1@/ changes and will transform the current value
-- of the property before applying it to the \"value\" property of /@adjustment2@/.
-- 
-- Vice versa, the /@fahrenheitToCelsius@/ function will be called whenever
-- the \"value\" property of /@adjustment2@/ changes, and will transform the
-- current value of the property before applying it to the \"value\" property
-- of /@adjustment1@/.
-- 
-- Note that t'GI.GObject.Objects.Binding.Binding' does not resolve cycles by itself; a cycle like
-- 
-- >
-- >  object1:propertyA -> object2:propertyB
-- >  object2:propertyB -> object3:propertyC
-- >  object3:propertyC -> object1:propertyA
-- 
-- 
-- might lead to an infinite loop. The loop, in this particular case,
-- can be avoided if the objects emit the [notify]("GI.GObject.Objects.Object#g:signal:notify") signal only
-- if the value has effectively been changed. A binding is implemented
-- using the [notify]("GI.GObject.Objects.Object#g:signal:notify") signal, so it is susceptible to all the
-- various ways of blocking a signal emission, like 'GI.GObject.Functions.signalStopEmission'
-- or 'GI.GObject.Functions.signalHandlerBlock'.
-- 
-- A binding will be severed, and the resources it allocates freed, whenever
-- either one of the t'GI.GObject.Objects.Object.Object' instances it refers to are finalized, or when
-- the t'GI.GObject.Objects.Binding.Binding' instance loses its last reference.
-- 
-- Bindings for languages with garbage collection can use
-- 'GI.GObject.Objects.Binding.bindingUnbind' to explicitly release a binding between the source
-- and target properties, instead of relying on the last reference on the
-- binding, source, and target instances to drop.
-- 
-- t'GI.GObject.Objects.Binding.Binding' is available since GObject 2.26
-- 
-- /Since: 2.26/

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

module GI.GObject.Objects.Binding
    ( 

-- * Exported types
    Binding(..)                             ,
    IsBinding                               ,
    toBinding                               ,


 -- * 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"), [unbind]("GI.GObject.Objects.Binding#g:method:unbind"), [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"), [getFlags]("GI.GObject.Objects.Binding#g:method:getFlags"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getSource]("GI.GObject.Objects.Binding#g:method:getSource"), [getSourceProperty]("GI.GObject.Objects.Binding#g:method:getSourceProperty"), [getTarget]("GI.GObject.Objects.Binding#g:method:getTarget"), [getTargetProperty]("GI.GObject.Objects.Binding#g:method:getTargetProperty").
-- 
-- ==== 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)
    ResolveBindingMethod                    ,
#endif

-- ** getFlags #method:getFlags#

#if defined(ENABLE_OVERLOADING)
    BindingGetFlagsMethodInfo               ,
#endif
    bindingGetFlags                         ,


-- ** getSource #method:getSource#

#if defined(ENABLE_OVERLOADING)
    BindingGetSourceMethodInfo              ,
#endif
    bindingGetSource                        ,


-- ** getSourceProperty #method:getSourceProperty#

#if defined(ENABLE_OVERLOADING)
    BindingGetSourcePropertyMethodInfo      ,
#endif
    bindingGetSourceProperty                ,


-- ** getTarget #method:getTarget#

#if defined(ENABLE_OVERLOADING)
    BindingGetTargetMethodInfo              ,
#endif
    bindingGetTarget                        ,


-- ** getTargetProperty #method:getTargetProperty#

#if defined(ENABLE_OVERLOADING)
    BindingGetTargetPropertyMethodInfo      ,
#endif
    bindingGetTargetProperty                ,


-- ** unbind #method:unbind#

#if defined(ENABLE_OVERLOADING)
    BindingUnbindMethodInfo                 ,
#endif
    bindingUnbind                           ,




 -- * Properties


-- ** flags #attr:flags#
-- | Flags to be used to control the t'GI.GObject.Objects.Binding.Binding'
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    BindingFlagsPropertyInfo                ,
#endif
#if defined(ENABLE_OVERLOADING)
    bindingFlags                            ,
#endif
    constructBindingFlags                   ,
    getBindingFlags                         ,


-- ** source #attr:source#
-- | The t'GI.GObject.Objects.Object.Object' that should be used as the source of the binding
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    BindingSourcePropertyInfo               ,
#endif
#if defined(ENABLE_OVERLOADING)
    bindingSource                           ,
#endif
    constructBindingSource                  ,
    getBindingSource                        ,


-- ** sourceProperty #attr:sourceProperty#
-- | The name of the property of t'GI.GObject.Objects.Binding.Binding':@/source/@ that should be used
-- as the source of the binding.
-- 
-- This should be in [canonical form][canonical-parameter-names] to get the
-- best performance.
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    BindingSourcePropertyPropertyInfo       ,
#endif
#if defined(ENABLE_OVERLOADING)
    bindingSourceProperty                   ,
#endif
    constructBindingSourceProperty          ,
    getBindingSourceProperty                ,


-- ** target #attr:target#
-- | The t'GI.GObject.Objects.Object.Object' that should be used as the target of the binding
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    BindingTargetPropertyInfo               ,
#endif
#if defined(ENABLE_OVERLOADING)
    bindingTarget                           ,
#endif
    constructBindingTarget                  ,
    getBindingTarget                        ,


-- ** targetProperty #attr:targetProperty#
-- | The name of the property of t'GI.GObject.Objects.Binding.Binding':@/target/@ that should be used
-- as the target of the binding.
-- 
-- This should be in [canonical form][canonical-parameter-names] to get the
-- best performance.
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    BindingTargetPropertyPropertyInfo       ,
#endif
#if defined(ENABLE_OVERLOADING)
    bindingTargetProperty                   ,
#endif
    constructBindingTargetProperty          ,
    getBindingTargetProperty                ,




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

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

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

foreign import ccall "g_binding_get_type"
    c_g_binding_get_type :: IO B.Types.GType

instance B.Types.TypedObject Binding where
    glibType :: IO GType
glibType = IO GType
c_g_binding_get_type

instance B.Types.GObject Binding

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

instance O.HasParentTypes Binding
type instance O.ParentTypes Binding = '[GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveBindingMethod (t :: Symbol) (o :: *) :: * where
    ResolveBindingMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveBindingMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveBindingMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveBindingMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveBindingMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveBindingMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveBindingMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveBindingMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveBindingMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveBindingMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveBindingMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveBindingMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveBindingMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveBindingMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveBindingMethod "unbind" o = BindingUnbindMethodInfo
    ResolveBindingMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveBindingMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveBindingMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveBindingMethod "getFlags" o = BindingGetFlagsMethodInfo
    ResolveBindingMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveBindingMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveBindingMethod "getSource" o = BindingGetSourceMethodInfo
    ResolveBindingMethod "getSourceProperty" o = BindingGetSourcePropertyMethodInfo
    ResolveBindingMethod "getTarget" o = BindingGetTargetMethodInfo
    ResolveBindingMethod "getTargetProperty" o = BindingGetTargetPropertyMethodInfo
    ResolveBindingMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveBindingMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveBindingMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveBindingMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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

-- | Get the value of the “@flags@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' binding #flags
-- @
getBindingFlags :: (MonadIO m, IsBinding o) => o -> m [GObject.Flags.BindingFlags]
getBindingFlags :: forall (m :: * -> *) o.
(MonadIO m, IsBinding o) =>
o -> m [BindingFlags]
getBindingFlags o
obj = IO [BindingFlags] -> m [BindingFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO [BindingFlags] -> m [BindingFlags])
-> IO [BindingFlags] -> m [BindingFlags]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO [BindingFlags]
forall a b.
(GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
B.Properties.getObjectPropertyFlags o
obj String
"flags"

-- | Construct a `GValueConstruct` with valid value for the “@flags@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructBindingFlags :: (IsBinding o, MIO.MonadIO m) => [GObject.Flags.BindingFlags] -> m (GValueConstruct o)
constructBindingFlags :: forall o (m :: * -> *).
(IsBinding o, MonadIO m) =>
[BindingFlags] -> m (GValueConstruct o)
constructBindingFlags [BindingFlags]
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 -> [BindingFlags] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags String
"flags" [BindingFlags]
val

#if defined(ENABLE_OVERLOADING)
data BindingFlagsPropertyInfo
instance AttrInfo BindingFlagsPropertyInfo where
    type AttrAllowedOps BindingFlagsPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint BindingFlagsPropertyInfo = IsBinding
    type AttrSetTypeConstraint BindingFlagsPropertyInfo = (~) [GObject.Flags.BindingFlags]
    type AttrTransferTypeConstraint BindingFlagsPropertyInfo = (~) [GObject.Flags.BindingFlags]
    type AttrTransferType BindingFlagsPropertyInfo = [GObject.Flags.BindingFlags]
    type AttrGetType BindingFlagsPropertyInfo = [GObject.Flags.BindingFlags]
    type AttrLabel BindingFlagsPropertyInfo = "flags"
    type AttrOrigin BindingFlagsPropertyInfo = Binding
    attrGet = getBindingFlags
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructBindingFlags
    attrClear = undefined
#endif

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

-- | Get the value of the “@source@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' binding #source
-- @
getBindingSource :: (MonadIO m, IsBinding o) => o -> m GObject.Object.Object
getBindingSource :: forall (m :: * -> *) o. (MonadIO m, IsBinding o) => o -> m Object
getBindingSource o
obj = IO Object -> m Object
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
"getBindingSource" (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
"source" ManagedPtr Object -> Object
GObject.Object.Object

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

#if defined(ENABLE_OVERLOADING)
data BindingSourcePropertyInfo
instance AttrInfo BindingSourcePropertyInfo where
    type AttrAllowedOps BindingSourcePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint BindingSourcePropertyInfo = IsBinding
    type AttrSetTypeConstraint BindingSourcePropertyInfo = GObject.Object.IsObject
    type AttrTransferTypeConstraint BindingSourcePropertyInfo = GObject.Object.IsObject
    type AttrTransferType BindingSourcePropertyInfo = GObject.Object.Object
    type AttrGetType BindingSourcePropertyInfo = GObject.Object.Object
    type AttrLabel BindingSourcePropertyInfo = "source"
    type AttrOrigin BindingSourcePropertyInfo = Binding
    attrGet = getBindingSource
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo GObject.Object.Object v
    attrConstruct = constructBindingSource
    attrClear = undefined
#endif

-- VVV Prop "source-property"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

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

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

#if defined(ENABLE_OVERLOADING)
data BindingSourcePropertyPropertyInfo
instance AttrInfo BindingSourcePropertyPropertyInfo where
    type AttrAllowedOps BindingSourcePropertyPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint BindingSourcePropertyPropertyInfo = IsBinding
    type AttrSetTypeConstraint BindingSourcePropertyPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint BindingSourcePropertyPropertyInfo = (~) T.Text
    type AttrTransferType BindingSourcePropertyPropertyInfo = T.Text
    type AttrGetType BindingSourcePropertyPropertyInfo = T.Text
    type AttrLabel BindingSourcePropertyPropertyInfo = "source-property"
    type AttrOrigin BindingSourcePropertyPropertyInfo = Binding
    attrGet = getBindingSourceProperty
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructBindingSourceProperty
    attrClear = undefined
#endif

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

-- | Get the value of the “@target@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' binding #target
-- @
getBindingTarget :: (MonadIO m, IsBinding o) => o -> m GObject.Object.Object
getBindingTarget :: forall (m :: * -> *) o. (MonadIO m, IsBinding o) => o -> m Object
getBindingTarget o
obj = IO Object -> m Object
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
"getBindingTarget" (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
"target" ManagedPtr Object -> Object
GObject.Object.Object

-- | Construct a `GValueConstruct` with valid value for the “@target@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructBindingTarget :: (IsBinding o, MIO.MonadIO m, GObject.Object.IsObject a) => a -> m (GValueConstruct o)
constructBindingTarget :: forall o (m :: * -> *) a.
(IsBinding o, MonadIO m, IsObject a) =>
a -> m (GValueConstruct o)
constructBindingTarget a
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 -> 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 BindingTargetPropertyInfo
instance AttrInfo BindingTargetPropertyInfo where
    type AttrAllowedOps BindingTargetPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint BindingTargetPropertyInfo = IsBinding
    type AttrSetTypeConstraint BindingTargetPropertyInfo = GObject.Object.IsObject
    type AttrTransferTypeConstraint BindingTargetPropertyInfo = GObject.Object.IsObject
    type AttrTransferType BindingTargetPropertyInfo = GObject.Object.Object
    type AttrGetType BindingTargetPropertyInfo = GObject.Object.Object
    type AttrLabel BindingTargetPropertyInfo = "target"
    type AttrOrigin BindingTargetPropertyInfo = Binding
    attrGet = getBindingTarget
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo GObject.Object.Object v
    attrConstruct = constructBindingTarget
    attrClear = undefined
#endif

-- VVV Prop "target-property"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

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

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

#if defined(ENABLE_OVERLOADING)
data BindingTargetPropertyPropertyInfo
instance AttrInfo BindingTargetPropertyPropertyInfo where
    type AttrAllowedOps BindingTargetPropertyPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint BindingTargetPropertyPropertyInfo = IsBinding
    type AttrSetTypeConstraint BindingTargetPropertyPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint BindingTargetPropertyPropertyInfo = (~) T.Text
    type AttrTransferType BindingTargetPropertyPropertyInfo = T.Text
    type AttrGetType BindingTargetPropertyPropertyInfo = T.Text
    type AttrLabel BindingTargetPropertyPropertyInfo = "target-property"
    type AttrOrigin BindingTargetPropertyPropertyInfo = Binding
    attrGet = getBindingTargetProperty
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructBindingTargetProperty
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Binding
type instance O.AttributeList Binding = BindingAttributeList
type BindingAttributeList = ('[ '("flags", BindingFlagsPropertyInfo), '("source", BindingSourcePropertyInfo), '("sourceProperty", BindingSourcePropertyPropertyInfo), '("target", BindingTargetPropertyInfo), '("targetProperty", BindingTargetPropertyPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
bindingFlags :: AttrLabelProxy "flags"
bindingFlags = AttrLabelProxy

bindingSource :: AttrLabelProxy "source"
bindingSource = AttrLabelProxy

bindingSourceProperty :: AttrLabelProxy "sourceProperty"
bindingSourceProperty = AttrLabelProxy

bindingTarget :: AttrLabelProxy "target"
bindingTarget = AttrLabelProxy

bindingTargetProperty :: AttrLabelProxy "targetProperty"
bindingTargetProperty = AttrLabelProxy

#endif

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

#endif

-- method Binding::get_flags
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "binding"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Binding" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBinding" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GObject" , name = "BindingFlags" })
-- throws : False
-- Skip return : False

foreign import ccall "g_binding_get_flags" g_binding_get_flags :: 
    Ptr Binding ->                          -- binding : TInterface (Name {namespace = "GObject", name = "Binding"})
    IO CUInt

-- | Retrieves the flags passed when constructing the t'GI.GObject.Objects.Binding.Binding'.
-- 
-- /Since: 2.26/
bindingGetFlags ::
    (B.CallStack.HasCallStack, MonadIO m, IsBinding a) =>
    a
    -- ^ /@binding@/: a t'GI.GObject.Objects.Binding.Binding'
    -> m [GObject.Flags.BindingFlags]
    -- ^ __Returns:__ the t'GI.GObject.Flags.BindingFlags' used by the t'GI.GObject.Objects.Binding.Binding'
bindingGetFlags :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBinding a) =>
a -> m [BindingFlags]
bindingGetFlags a
binding = IO [BindingFlags] -> m [BindingFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [BindingFlags] -> m [BindingFlags])
-> IO [BindingFlags] -> m [BindingFlags]
forall a b. (a -> b) -> a -> b
$ do
    Ptr Binding
binding' <- a -> IO (Ptr Binding)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
binding
    CUInt
result <- Ptr Binding -> IO CUInt
g_binding_get_flags Ptr Binding
binding'
    let result' :: [BindingFlags]
result' = CUInt -> [BindingFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
binding
    [BindingFlags] -> IO [BindingFlags]
forall (m :: * -> *) a. Monad m => a -> m a
return [BindingFlags]
result'

#if defined(ENABLE_OVERLOADING)
data BindingGetFlagsMethodInfo
instance (signature ~ (m [GObject.Flags.BindingFlags]), MonadIO m, IsBinding a) => O.OverloadedMethod BindingGetFlagsMethodInfo a signature where
    overloadedMethod = bindingGetFlags

instance O.OverloadedMethodInfo BindingGetFlagsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GObject.Objects.Binding.bindingGetFlags",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gobject-2.0.26/docs/GI-GObject-Objects-Binding.html#v:bindingGetFlags"
        }


#endif

-- method Binding::get_source
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "binding"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Binding" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBinding" , 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 "g_binding_get_source" g_binding_get_source :: 
    Ptr Binding ->                          -- binding : TInterface (Name {namespace = "GObject", name = "Binding"})
    IO (Ptr GObject.Object.Object)

-- | Retrieves the t'GI.GObject.Objects.Object.Object' instance used as the source of the binding.
-- 
-- /Since: 2.26/
bindingGetSource ::
    (B.CallStack.HasCallStack, MonadIO m, IsBinding a) =>
    a
    -- ^ /@binding@/: a t'GI.GObject.Objects.Binding.Binding'
    -> m GObject.Object.Object
    -- ^ __Returns:__ the source t'GI.GObject.Objects.Object.Object'
bindingGetSource :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBinding a) =>
a -> m Object
bindingGetSource a
binding = IO Object -> m Object
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 Binding
binding' <- a -> IO (Ptr Binding)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
binding
    Ptr Object
result <- Ptr Binding -> IO (Ptr Object)
g_binding_get_source Ptr Binding
binding'
    Text -> Ptr Object -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"bindingGetSource" 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
binding
    Object -> IO Object
forall (m :: * -> *) a. Monad m => a -> m a
return Object
result'

#if defined(ENABLE_OVERLOADING)
data BindingGetSourceMethodInfo
instance (signature ~ (m GObject.Object.Object), MonadIO m, IsBinding a) => O.OverloadedMethod BindingGetSourceMethodInfo a signature where
    overloadedMethod = bindingGetSource

instance O.OverloadedMethodInfo BindingGetSourceMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GObject.Objects.Binding.bindingGetSource",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gobject-2.0.26/docs/GI-GObject-Objects-Binding.html#v:bindingGetSource"
        }


#endif

-- method Binding::get_source_property
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "binding"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Binding" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBinding" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_binding_get_source_property" g_binding_get_source_property :: 
    Ptr Binding ->                          -- binding : TInterface (Name {namespace = "GObject", name = "Binding"})
    IO CString

-- | Retrieves the name of the property of t'GI.GObject.Objects.Binding.Binding':@/source/@ used as the source
-- of the binding.
-- 
-- /Since: 2.26/
bindingGetSourceProperty ::
    (B.CallStack.HasCallStack, MonadIO m, IsBinding a) =>
    a
    -- ^ /@binding@/: a t'GI.GObject.Objects.Binding.Binding'
    -> m T.Text
    -- ^ __Returns:__ the name of the source property
bindingGetSourceProperty :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBinding a) =>
a -> m Text
bindingGetSourceProperty a
binding = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr Binding
binding' <- a -> IO (Ptr Binding)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
binding
    CString
result <- Ptr Binding -> IO CString
g_binding_get_source_property Ptr Binding
binding'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"bindingGetSourceProperty" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
binding
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data BindingGetSourcePropertyMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsBinding a) => O.OverloadedMethod BindingGetSourcePropertyMethodInfo a signature where
    overloadedMethod = bindingGetSourceProperty

instance O.OverloadedMethodInfo BindingGetSourcePropertyMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GObject.Objects.Binding.bindingGetSourceProperty",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gobject-2.0.26/docs/GI-GObject-Objects-Binding.html#v:bindingGetSourceProperty"
        }


#endif

-- method Binding::get_target
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "binding"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Binding" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBinding" , 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 "g_binding_get_target" g_binding_get_target :: 
    Ptr Binding ->                          -- binding : TInterface (Name {namespace = "GObject", name = "Binding"})
    IO (Ptr GObject.Object.Object)

-- | Retrieves the t'GI.GObject.Objects.Object.Object' instance used as the target of the binding.
-- 
-- /Since: 2.26/
bindingGetTarget ::
    (B.CallStack.HasCallStack, MonadIO m, IsBinding a) =>
    a
    -- ^ /@binding@/: a t'GI.GObject.Objects.Binding.Binding'
    -> m GObject.Object.Object
    -- ^ __Returns:__ the target t'GI.GObject.Objects.Object.Object'
bindingGetTarget :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBinding a) =>
a -> m Object
bindingGetTarget a
binding = IO Object -> m Object
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 Binding
binding' <- a -> IO (Ptr Binding)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
binding
    Ptr Object
result <- Ptr Binding -> IO (Ptr Object)
g_binding_get_target Ptr Binding
binding'
    Text -> Ptr Object -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"bindingGetTarget" 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
binding
    Object -> IO Object
forall (m :: * -> *) a. Monad m => a -> m a
return Object
result'

#if defined(ENABLE_OVERLOADING)
data BindingGetTargetMethodInfo
instance (signature ~ (m GObject.Object.Object), MonadIO m, IsBinding a) => O.OverloadedMethod BindingGetTargetMethodInfo a signature where
    overloadedMethod = bindingGetTarget

instance O.OverloadedMethodInfo BindingGetTargetMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GObject.Objects.Binding.bindingGetTarget",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gobject-2.0.26/docs/GI-GObject-Objects-Binding.html#v:bindingGetTarget"
        }


#endif

-- method Binding::get_target_property
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "binding"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Binding" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBinding" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_binding_get_target_property" g_binding_get_target_property :: 
    Ptr Binding ->                          -- binding : TInterface (Name {namespace = "GObject", name = "Binding"})
    IO CString

-- | Retrieves the name of the property of t'GI.GObject.Objects.Binding.Binding':@/target/@ used as the target
-- of the binding.
-- 
-- /Since: 2.26/
bindingGetTargetProperty ::
    (B.CallStack.HasCallStack, MonadIO m, IsBinding a) =>
    a
    -- ^ /@binding@/: a t'GI.GObject.Objects.Binding.Binding'
    -> m T.Text
    -- ^ __Returns:__ the name of the target property
bindingGetTargetProperty :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBinding a) =>
a -> m Text
bindingGetTargetProperty a
binding = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr Binding
binding' <- a -> IO (Ptr Binding)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
binding
    CString
result <- Ptr Binding -> IO CString
g_binding_get_target_property Ptr Binding
binding'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"bindingGetTargetProperty" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
binding
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data BindingGetTargetPropertyMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsBinding a) => O.OverloadedMethod BindingGetTargetPropertyMethodInfo a signature where
    overloadedMethod = bindingGetTargetProperty

instance O.OverloadedMethodInfo BindingGetTargetPropertyMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GObject.Objects.Binding.bindingGetTargetProperty",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gobject-2.0.26/docs/GI-GObject-Objects-Binding.html#v:bindingGetTargetProperty"
        }


#endif

-- method Binding::unbind
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "binding"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Binding" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBinding" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_binding_unbind" g_binding_unbind :: 
    Ptr Binding ->                          -- binding : TInterface (Name {namespace = "GObject", name = "Binding"})
    IO ()

-- | Explicitly releases the binding between the source and the target
-- property expressed by /@binding@/.
-- 
-- This function will release the reference that is being held on
-- the /@binding@/ instance; if you want to hold on to the t'GI.GObject.Objects.Binding.Binding' instance
-- after calling 'GI.GObject.Objects.Binding.bindingUnbind', you will need to hold a reference
-- to it.
-- 
-- /Since: 2.38/
bindingUnbind ::
    (B.CallStack.HasCallStack, MonadIO m, IsBinding a) =>
    a
    -- ^ /@binding@/: a t'GI.GObject.Objects.Binding.Binding'
    -> m ()
bindingUnbind :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBinding a) =>
a -> m ()
bindingUnbind a
binding = 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 Binding
binding' <- a -> IO (Ptr Binding)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
binding
    Ptr Binding -> IO ()
g_binding_unbind Ptr Binding
binding'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
binding
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BindingUnbindMethodInfo
instance (signature ~ (m ()), MonadIO m, IsBinding a) => O.OverloadedMethod BindingUnbindMethodInfo a signature where
    overloadedMethod = bindingUnbind

instance O.OverloadedMethodInfo BindingUnbindMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GObject.Objects.Binding.bindingUnbind",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gobject-2.0.26/docs/GI-GObject-Objects-Binding.html#v:bindingUnbind"
        }


#endif