{-# 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#signal:notify") signal only
-- if the value has effectively been changed. A binding is implemented
-- using the [notify]("GI.GObject.Objects.Object#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                               ,
    noBinding                               ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#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
-- 
-- /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
-- 
-- /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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified 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 {-# 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 (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)
foreign import ccall "g_binding_get_type"
    c_g_binding_get_type :: IO GType

instance GObject Binding where
    gobjectType :: IO GType
gobjectType = IO GType
c_g_binding_get_type
    

-- | Convert 'Binding' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue Binding where
    toGValue :: Binding -> IO GValue
toGValue o :: Binding
o = do
        GType
gtype <- IO GType
c_g_binding_get_type
        Binding -> (Ptr Binding -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Binding
o (GType
-> (GValue -> Ptr Binding -> IO ()) -> Ptr Binding -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Binding -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO Binding
fromGValue gv :: GValue
gv = do
        Ptr Binding
ptr <- GValue -> IO (Ptr Binding)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Binding)
        (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
        
    

-- | Type class for types which can be safely cast to `Binding`, for instance with `toBinding`.
class (GObject o, O.IsDescendantOf Binding o) => IsBinding o
instance (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 :: (MonadIO m, IsBinding o) => o -> m Binding
toBinding :: o -> m Binding
toBinding = IO Binding -> m Binding
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Binding -> Binding
Binding

-- | A convenience alias for `Nothing` :: `Maybe` `Binding`.
noBinding :: Maybe Binding
noBinding :: Maybe Binding
noBinding = Maybe Binding
forall a. Maybe a
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.MethodInfo 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

#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 :: o -> m [BindingFlags]
getBindingFlags obj :: o
obj = 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
$ o -> String -> IO [BindingFlags]
forall a b.
(GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
B.Properties.getObjectPropertyFlags o
obj "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) => [GObject.Flags.BindingFlags] -> IO (GValueConstruct o)
constructBindingFlags :: [BindingFlags] -> IO (GValueConstruct o)
constructBindingFlags val :: [BindingFlags]
val = String -> [BindingFlags] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags "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 :: o -> m Object
getBindingSource obj :: o
obj = 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
$ Text -> IO (Maybe Object) -> IO Object
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing "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 "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, GObject.Object.IsObject a) => a -> IO (GValueConstruct o)
constructBindingSource :: a -> IO (GValueConstruct o)
constructBindingSource val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "source" (a -> Maybe a
forall a. a -> Maybe a
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 :: o -> m Text
getBindingSourceProperty obj :: o
obj = 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
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing "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 "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) => T.Text -> IO (GValueConstruct o)
constructBindingSourceProperty :: Text -> IO (GValueConstruct o)
constructBindingSourceProperty val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "source-property" (Text -> Maybe Text
forall a. a -> Maybe a
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 :: o -> m Object
getBindingTarget obj :: o
obj = 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
$ Text -> IO (Maybe Object) -> IO Object
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing "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 "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, GObject.Object.IsObject a) => a -> IO (GValueConstruct o)
constructBindingTarget :: a -> IO (GValueConstruct o)
constructBindingTarget val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "target" (a -> Maybe a
forall a. a -> Maybe a
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 :: o -> m Text
getBindingTargetProperty obj :: o
obj = 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
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing "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 "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) => T.Text -> IO (GValueConstruct o)
constructBindingTargetProperty :: Text -> IO (GValueConstruct o)
constructBindingTargetProperty val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "target-property" (Text -> Maybe Text
forall a. a -> Maybe a
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 :: a -> m [BindingFlags]
bindingGetFlags binding :: 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.MethodInfo BindingGetFlagsMethodInfo a signature where
    overloadedMethod = 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 :: a -> m Object
bindingGetSource binding :: 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 "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.MethodInfo BindingGetSourceMethodInfo a signature where
    overloadedMethod = 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 :: a -> m Text
bindingGetSourceProperty binding :: 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 "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.MethodInfo BindingGetSourcePropertyMethodInfo a signature where
    overloadedMethod = 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 :: a -> m Object
bindingGetTarget binding :: 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 "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.MethodInfo BindingGetTargetMethodInfo a signature where
    overloadedMethod = 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 :: a -> m Text
bindingGetTargetProperty binding :: 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 "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.MethodInfo BindingGetTargetPropertyMethodInfo a signature where
    overloadedMethod = 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 :: a -> m ()
bindingUnbind binding :: 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.MethodInfo BindingUnbindMethodInfo a signature where
    overloadedMethod = bindingUnbind

#endif