module GI.GObject.Objects.Binding
(
Binding(..) ,
BindingK ,
toBinding ,
noBinding ,
bindingGetFlags ,
bindingGetSource ,
bindingGetSourceProperty ,
bindingGetTarget ,
bindingGetTargetProperty ,
bindingUnbind ,
BindingFlagsPropertyInfo ,
constructBindingFlags ,
getBindingFlags ,
BindingSourcePropertyInfo ,
constructBindingSource ,
getBindingSource ,
BindingSourcePropertyPropertyInfo ,
constructBindingSourceProperty ,
getBindingSourceProperty ,
BindingTargetPropertyInfo ,
constructBindingTarget ,
getBindingTarget ,
BindingTargetPropertyPropertyInfo ,
constructBindingTargetProperty ,
getBindingTargetProperty ,
) where
import Prelude ()
import Data.GI.Base.ShortPrelude
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import GI.GObject.Types
import GI.GObject.Callbacks
newtype Binding = Binding (ForeignPtr Binding)
foreign import ccall "g_binding_get_type"
c_g_binding_get_type :: IO GType
type instance ParentTypes Binding = BindingParentTypes
type BindingParentTypes = '[Object]
instance GObject Binding where
gobjectIsInitiallyUnowned _ = False
gobjectType _ = c_g_binding_get_type
class GObject o => BindingK o
instance (GObject o, IsDescendantOf Binding o) => BindingK o
toBinding :: BindingK o => o -> IO Binding
toBinding = unsafeCastTo Binding
noBinding :: Maybe Binding
noBinding = Nothing
getBindingFlags :: (MonadIO m, BindingK o) => o -> m [BindingFlags]
getBindingFlags obj = liftIO $ getObjectPropertyFlags obj "flags"
constructBindingFlags :: [BindingFlags] -> IO ([Char], GValue)
constructBindingFlags val = constructObjectPropertyFlags "flags" val
data BindingFlagsPropertyInfo
instance AttrInfo BindingFlagsPropertyInfo where
type AttrAllowedOps BindingFlagsPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint BindingFlagsPropertyInfo = (~) [BindingFlags]
type AttrBaseTypeConstraint BindingFlagsPropertyInfo = BindingK
type AttrGetType BindingFlagsPropertyInfo = [BindingFlags]
type AttrLabel BindingFlagsPropertyInfo = "Binding::flags"
attrGet _ = getBindingFlags
attrSet _ = undefined
attrConstruct _ = constructBindingFlags
getBindingSource :: (MonadIO m, BindingK o) => o -> m Object
getBindingSource obj = liftIO $ getObjectPropertyObject obj "source" Object
constructBindingSource :: (ObjectK a) => a -> IO ([Char], GValue)
constructBindingSource val = constructObjectPropertyObject "source" val
data BindingSourcePropertyInfo
instance AttrInfo BindingSourcePropertyInfo where
type AttrAllowedOps BindingSourcePropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint BindingSourcePropertyInfo = ObjectK
type AttrBaseTypeConstraint BindingSourcePropertyInfo = BindingK
type AttrGetType BindingSourcePropertyInfo = Object
type AttrLabel BindingSourcePropertyInfo = "Binding::source"
attrGet _ = getBindingSource
attrSet _ = undefined
attrConstruct _ = constructBindingSource
getBindingSourceProperty :: (MonadIO m, BindingK o) => o -> m T.Text
getBindingSourceProperty obj = liftIO $ getObjectPropertyString obj "source-property"
constructBindingSourceProperty :: T.Text -> IO ([Char], GValue)
constructBindingSourceProperty val = constructObjectPropertyString "source-property" val
data BindingSourcePropertyPropertyInfo
instance AttrInfo BindingSourcePropertyPropertyInfo where
type AttrAllowedOps BindingSourcePropertyPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint BindingSourcePropertyPropertyInfo = (~) T.Text
type AttrBaseTypeConstraint BindingSourcePropertyPropertyInfo = BindingK
type AttrGetType BindingSourcePropertyPropertyInfo = T.Text
type AttrLabel BindingSourcePropertyPropertyInfo = "Binding::source-property"
attrGet _ = getBindingSourceProperty
attrSet _ = undefined
attrConstruct _ = constructBindingSourceProperty
getBindingTarget :: (MonadIO m, BindingK o) => o -> m Object
getBindingTarget obj = liftIO $ getObjectPropertyObject obj "target" Object
constructBindingTarget :: (ObjectK a) => a -> IO ([Char], GValue)
constructBindingTarget val = constructObjectPropertyObject "target" val
data BindingTargetPropertyInfo
instance AttrInfo BindingTargetPropertyInfo where
type AttrAllowedOps BindingTargetPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint BindingTargetPropertyInfo = ObjectK
type AttrBaseTypeConstraint BindingTargetPropertyInfo = BindingK
type AttrGetType BindingTargetPropertyInfo = Object
type AttrLabel BindingTargetPropertyInfo = "Binding::target"
attrGet _ = getBindingTarget
attrSet _ = undefined
attrConstruct _ = constructBindingTarget
getBindingTargetProperty :: (MonadIO m, BindingK o) => o -> m T.Text
getBindingTargetProperty obj = liftIO $ getObjectPropertyString obj "target-property"
constructBindingTargetProperty :: T.Text -> IO ([Char], GValue)
constructBindingTargetProperty val = constructObjectPropertyString "target-property" val
data BindingTargetPropertyPropertyInfo
instance AttrInfo BindingTargetPropertyPropertyInfo where
type AttrAllowedOps BindingTargetPropertyPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint BindingTargetPropertyPropertyInfo = (~) T.Text
type AttrBaseTypeConstraint BindingTargetPropertyPropertyInfo = BindingK
type AttrGetType BindingTargetPropertyPropertyInfo = T.Text
type AttrLabel BindingTargetPropertyPropertyInfo = "Binding::target-property"
attrGet _ = getBindingTargetProperty
attrSet _ = undefined
attrConstruct _ = constructBindingTargetProperty
type instance AttributeList Binding = BindingAttributeList
type BindingAttributeList = ('[ '("flags", BindingFlagsPropertyInfo), '("source", BindingSourcePropertyInfo), '("source-property", BindingSourcePropertyPropertyInfo), '("target", BindingTargetPropertyInfo), '("target-property", BindingTargetPropertyPropertyInfo)] :: [(Symbol, *)])
type instance SignalList Binding = BindingSignalList
type BindingSignalList = ('[ '("notify", ObjectNotifySignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])
foreign import ccall "g_binding_get_flags" g_binding_get_flags ::
Ptr Binding ->
IO CUInt
bindingGetFlags ::
(MonadIO m, BindingK a) =>
a ->
m [BindingFlags]
bindingGetFlags _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- g_binding_get_flags _obj'
let result' = wordToGFlags result
touchManagedPtr _obj
return result'
foreign import ccall "g_binding_get_source" g_binding_get_source ::
Ptr Binding ->
IO (Ptr Object)
bindingGetSource ::
(MonadIO m, BindingK a) =>
a ->
m Object
bindingGetSource _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- g_binding_get_source _obj'
checkUnexpectedReturnNULL "g_binding_get_source" result
result' <- (newObject Object) result
touchManagedPtr _obj
return result'
foreign import ccall "g_binding_get_source_property" g_binding_get_source_property ::
Ptr Binding ->
IO CString
bindingGetSourceProperty ::
(MonadIO m, BindingK a) =>
a ->
m T.Text
bindingGetSourceProperty _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- g_binding_get_source_property _obj'
checkUnexpectedReturnNULL "g_binding_get_source_property" result
result' <- cstringToText result
touchManagedPtr _obj
return result'
foreign import ccall "g_binding_get_target" g_binding_get_target ::
Ptr Binding ->
IO (Ptr Object)
bindingGetTarget ::
(MonadIO m, BindingK a) =>
a ->
m Object
bindingGetTarget _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- g_binding_get_target _obj'
checkUnexpectedReturnNULL "g_binding_get_target" result
result' <- (newObject Object) result
touchManagedPtr _obj
return result'
foreign import ccall "g_binding_get_target_property" g_binding_get_target_property ::
Ptr Binding ->
IO CString
bindingGetTargetProperty ::
(MonadIO m, BindingK a) =>
a ->
m T.Text
bindingGetTargetProperty _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- g_binding_get_target_property _obj'
checkUnexpectedReturnNULL "g_binding_get_target_property" result
result' <- cstringToText result
touchManagedPtr _obj
return result'
foreign import ccall "g_binding_unbind" g_binding_unbind ::
Ptr Binding ->
IO ()
bindingUnbind ::
(MonadIO m, BindingK a) =>
a ->
m ()
bindingUnbind _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
g_binding_unbind _obj'
touchManagedPtr _obj
return ()