{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.PropertyAction
(
PropertyAction(..) ,
IsPropertyAction ,
toPropertyAction ,
noPropertyAction ,
#if defined(ENABLE_OVERLOADING)
ResolvePropertyActionMethod ,
#endif
propertyActionNew ,
#if defined(ENABLE_OVERLOADING)
PropertyActionEnabledPropertyInfo ,
#endif
getPropertyActionEnabled ,
#if defined(ENABLE_OVERLOADING)
propertyActionEnabled ,
#endif
#if defined(ENABLE_OVERLOADING)
PropertyActionInvertBooleanPropertyInfo ,
#endif
constructPropertyActionInvertBoolean ,
getPropertyActionInvertBoolean ,
#if defined(ENABLE_OVERLOADING)
propertyActionInvertBoolean ,
#endif
#if defined(ENABLE_OVERLOADING)
PropertyActionNamePropertyInfo ,
#endif
constructPropertyActionName ,
getPropertyActionName ,
#if defined(ENABLE_OVERLOADING)
propertyActionName ,
#endif
#if defined(ENABLE_OVERLOADING)
PropertyActionObjectPropertyInfo ,
#endif
constructPropertyActionObject ,
#if defined(ENABLE_OVERLOADING)
propertyActionObject ,
#endif
#if defined(ENABLE_OVERLOADING)
PropertyActionParameterTypePropertyInfo ,
#endif
getPropertyActionParameterType ,
#if defined(ENABLE_OVERLOADING)
propertyActionParameterType ,
#endif
#if defined(ENABLE_OVERLOADING)
PropertyActionPropertyNamePropertyInfo ,
#endif
constructPropertyActionPropertyName ,
#if defined(ENABLE_OVERLOADING)
propertyActionPropertyName ,
#endif
#if defined(ENABLE_OVERLOADING)
PropertyActionStatePropertyInfo ,
#endif
getPropertyActionState ,
#if defined(ENABLE_OVERLOADING)
propertyActionState ,
#endif
#if defined(ENABLE_OVERLOADING)
PropertyActionStateTypePropertyInfo ,
#endif
getPropertyActionStateType ,
#if defined(ENABLE_OVERLOADING)
propertyActionStateType ,
#endif
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.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 qualified GI.GLib.Structs.VariantType as GLib.VariantType
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Action as Gio.Action
newtype PropertyAction = PropertyAction (ManagedPtr PropertyAction)
deriving (PropertyAction -> PropertyAction -> Bool
(PropertyAction -> PropertyAction -> Bool)
-> (PropertyAction -> PropertyAction -> Bool) -> Eq PropertyAction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PropertyAction -> PropertyAction -> Bool
$c/= :: PropertyAction -> PropertyAction -> Bool
== :: PropertyAction -> PropertyAction -> Bool
$c== :: PropertyAction -> PropertyAction -> Bool
Eq)
foreign import ccall "g_property_action_get_type"
c_g_property_action_get_type :: IO GType
instance GObject PropertyAction where
gobjectType :: IO GType
gobjectType = IO GType
c_g_property_action_get_type
instance B.GValue.IsGValue PropertyAction where
toGValue :: PropertyAction -> IO GValue
toGValue o :: PropertyAction
o = do
GType
gtype <- IO GType
c_g_property_action_get_type
PropertyAction -> (Ptr PropertyAction -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr PropertyAction
o (GType
-> (GValue -> Ptr PropertyAction -> IO ())
-> Ptr PropertyAction
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr PropertyAction -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO PropertyAction
fromGValue gv :: GValue
gv = do
Ptr PropertyAction
ptr <- GValue -> IO (Ptr PropertyAction)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr PropertyAction)
(ManagedPtr PropertyAction -> PropertyAction)
-> Ptr PropertyAction -> IO PropertyAction
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr PropertyAction -> PropertyAction
PropertyAction Ptr PropertyAction
ptr
class (GObject o, O.IsDescendantOf PropertyAction o) => IsPropertyAction o
instance (GObject o, O.IsDescendantOf PropertyAction o) => IsPropertyAction o
instance O.HasParentTypes PropertyAction
type instance O.ParentTypes PropertyAction = '[GObject.Object.Object, Gio.Action.Action]
toPropertyAction :: (MonadIO m, IsPropertyAction o) => o -> m PropertyAction
toPropertyAction :: o -> m PropertyAction
toPropertyAction = IO PropertyAction -> m PropertyAction
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PropertyAction -> m PropertyAction)
-> (o -> IO PropertyAction) -> o -> m PropertyAction
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr PropertyAction -> PropertyAction)
-> o -> IO PropertyAction
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr PropertyAction -> PropertyAction
PropertyAction
noPropertyAction :: Maybe PropertyAction
noPropertyAction :: Maybe PropertyAction
noPropertyAction = Maybe PropertyAction
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolvePropertyActionMethod (t :: Symbol) (o :: *) :: * where
ResolvePropertyActionMethod "activate" o = Gio.Action.ActionActivateMethodInfo
ResolvePropertyActionMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolvePropertyActionMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolvePropertyActionMethod "changeState" o = Gio.Action.ActionChangeStateMethodInfo
ResolvePropertyActionMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolvePropertyActionMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolvePropertyActionMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolvePropertyActionMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolvePropertyActionMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolvePropertyActionMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolvePropertyActionMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolvePropertyActionMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolvePropertyActionMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolvePropertyActionMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolvePropertyActionMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolvePropertyActionMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolvePropertyActionMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolvePropertyActionMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolvePropertyActionMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolvePropertyActionMethod "getEnabled" o = Gio.Action.ActionGetEnabledMethodInfo
ResolvePropertyActionMethod "getName" o = Gio.Action.ActionGetNameMethodInfo
ResolvePropertyActionMethod "getParameterType" o = Gio.Action.ActionGetParameterTypeMethodInfo
ResolvePropertyActionMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolvePropertyActionMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolvePropertyActionMethod "getState" o = Gio.Action.ActionGetStateMethodInfo
ResolvePropertyActionMethod "getStateHint" o = Gio.Action.ActionGetStateHintMethodInfo
ResolvePropertyActionMethod "getStateType" o = Gio.Action.ActionGetStateTypeMethodInfo
ResolvePropertyActionMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolvePropertyActionMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolvePropertyActionMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolvePropertyActionMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolvePropertyActionMethod t PropertyAction, O.MethodInfo info PropertyAction p) => OL.IsLabel t (PropertyAction -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
getPropertyActionEnabled :: (MonadIO m, IsPropertyAction o) => o -> m Bool
getPropertyActionEnabled :: o -> m Bool
getPropertyActionEnabled obj :: o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "enabled"
#if defined(ENABLE_OVERLOADING)
data PropertyActionEnabledPropertyInfo
instance AttrInfo PropertyActionEnabledPropertyInfo where
type AttrAllowedOps PropertyActionEnabledPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint PropertyActionEnabledPropertyInfo = IsPropertyAction
type AttrSetTypeConstraint PropertyActionEnabledPropertyInfo = (~) ()
type AttrTransferTypeConstraint PropertyActionEnabledPropertyInfo = (~) ()
type AttrTransferType PropertyActionEnabledPropertyInfo = ()
type AttrGetType PropertyActionEnabledPropertyInfo = Bool
type AttrLabel PropertyActionEnabledPropertyInfo = "enabled"
type AttrOrigin PropertyActionEnabledPropertyInfo = PropertyAction
attrGet = getPropertyActionEnabled
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
#endif
getPropertyActionInvertBoolean :: (MonadIO m, IsPropertyAction o) => o -> m Bool
getPropertyActionInvertBoolean :: o -> m Bool
getPropertyActionInvertBoolean obj :: o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "invert-boolean"
constructPropertyActionInvertBoolean :: (IsPropertyAction o) => Bool -> IO (GValueConstruct o)
constructPropertyActionInvertBoolean :: Bool -> IO (GValueConstruct o)
constructPropertyActionInvertBoolean val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "invert-boolean" Bool
val
#if defined(ENABLE_OVERLOADING)
data PropertyActionInvertBooleanPropertyInfo
instance AttrInfo PropertyActionInvertBooleanPropertyInfo where
type AttrAllowedOps PropertyActionInvertBooleanPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint PropertyActionInvertBooleanPropertyInfo = IsPropertyAction
type AttrSetTypeConstraint PropertyActionInvertBooleanPropertyInfo = (~) Bool
type AttrTransferTypeConstraint PropertyActionInvertBooleanPropertyInfo = (~) Bool
type AttrTransferType PropertyActionInvertBooleanPropertyInfo = Bool
type AttrGetType PropertyActionInvertBooleanPropertyInfo = Bool
type AttrLabel PropertyActionInvertBooleanPropertyInfo = "invert-boolean"
type AttrOrigin PropertyActionInvertBooleanPropertyInfo = PropertyAction
attrGet = getPropertyActionInvertBoolean
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructPropertyActionInvertBoolean
attrClear = undefined
#endif
getPropertyActionName :: (MonadIO m, IsPropertyAction o) => o -> m (Maybe T.Text)
getPropertyActionName :: o -> m (Maybe Text)
getPropertyActionName obj :: o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe 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 "name"
constructPropertyActionName :: (IsPropertyAction o) => T.Text -> IO (GValueConstruct o)
constructPropertyActionName :: Text -> IO (GValueConstruct o)
constructPropertyActionName val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
#if defined(ENABLE_OVERLOADING)
data PropertyActionNamePropertyInfo
instance AttrInfo PropertyActionNamePropertyInfo where
type AttrAllowedOps PropertyActionNamePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint PropertyActionNamePropertyInfo = IsPropertyAction
type AttrSetTypeConstraint PropertyActionNamePropertyInfo = (~) T.Text
type AttrTransferTypeConstraint PropertyActionNamePropertyInfo = (~) T.Text
type AttrTransferType PropertyActionNamePropertyInfo = T.Text
type AttrGetType PropertyActionNamePropertyInfo = (Maybe T.Text)
type AttrLabel PropertyActionNamePropertyInfo = "name"
type AttrOrigin PropertyActionNamePropertyInfo = PropertyAction
attrGet = getPropertyActionName
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructPropertyActionName
attrClear = undefined
#endif
constructPropertyActionObject :: (IsPropertyAction o, GObject.Object.IsObject a) => a -> IO (GValueConstruct o)
constructPropertyActionObject :: a -> IO (GValueConstruct o)
constructPropertyActionObject val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "object" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
#if defined(ENABLE_OVERLOADING)
data PropertyActionObjectPropertyInfo
instance AttrInfo PropertyActionObjectPropertyInfo where
type AttrAllowedOps PropertyActionObjectPropertyInfo = '[ 'AttrConstruct, 'AttrClear]
type AttrBaseTypeConstraint PropertyActionObjectPropertyInfo = IsPropertyAction
type AttrSetTypeConstraint PropertyActionObjectPropertyInfo = GObject.Object.IsObject
type AttrTransferTypeConstraint PropertyActionObjectPropertyInfo = GObject.Object.IsObject
type AttrTransferType PropertyActionObjectPropertyInfo = GObject.Object.Object
type AttrGetType PropertyActionObjectPropertyInfo = ()
type AttrLabel PropertyActionObjectPropertyInfo = "object"
type AttrOrigin PropertyActionObjectPropertyInfo = PropertyAction
attrGet = undefined
attrSet = undefined
attrTransfer _ v = do
unsafeCastTo GObject.Object.Object v
attrConstruct = constructPropertyActionObject
attrClear = undefined
#endif
getPropertyActionParameterType :: (MonadIO m, IsPropertyAction o) => o -> m (Maybe GLib.VariantType.VariantType)
getPropertyActionParameterType :: o -> m (Maybe VariantType)
getPropertyActionParameterType obj :: o
obj = IO (Maybe VariantType) -> m (Maybe VariantType)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe VariantType) -> m (Maybe VariantType))
-> IO (Maybe VariantType) -> m (Maybe VariantType)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr VariantType -> VariantType)
-> IO (Maybe VariantType)
forall a b.
(GObject a, BoxedObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj "parameter-type" ManagedPtr VariantType -> VariantType
GLib.VariantType.VariantType
#if defined(ENABLE_OVERLOADING)
data PropertyActionParameterTypePropertyInfo
instance AttrInfo PropertyActionParameterTypePropertyInfo where
type AttrAllowedOps PropertyActionParameterTypePropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint PropertyActionParameterTypePropertyInfo = IsPropertyAction
type AttrSetTypeConstraint PropertyActionParameterTypePropertyInfo = (~) ()
type AttrTransferTypeConstraint PropertyActionParameterTypePropertyInfo = (~) ()
type AttrTransferType PropertyActionParameterTypePropertyInfo = ()
type AttrGetType PropertyActionParameterTypePropertyInfo = (Maybe GLib.VariantType.VariantType)
type AttrLabel PropertyActionParameterTypePropertyInfo = "parameter-type"
type AttrOrigin PropertyActionParameterTypePropertyInfo = PropertyAction
attrGet = getPropertyActionParameterType
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
#endif
constructPropertyActionPropertyName :: (IsPropertyAction o) => T.Text -> IO (GValueConstruct o)
constructPropertyActionPropertyName :: Text -> IO (GValueConstruct o)
constructPropertyActionPropertyName val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "property-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
#if defined(ENABLE_OVERLOADING)
data PropertyActionPropertyNamePropertyInfo
instance AttrInfo PropertyActionPropertyNamePropertyInfo where
type AttrAllowedOps PropertyActionPropertyNamePropertyInfo = '[ 'AttrConstruct, 'AttrClear]
type AttrBaseTypeConstraint PropertyActionPropertyNamePropertyInfo = IsPropertyAction
type AttrSetTypeConstraint PropertyActionPropertyNamePropertyInfo = (~) T.Text
type AttrTransferTypeConstraint PropertyActionPropertyNamePropertyInfo = (~) T.Text
type AttrTransferType PropertyActionPropertyNamePropertyInfo = T.Text
type AttrGetType PropertyActionPropertyNamePropertyInfo = ()
type AttrLabel PropertyActionPropertyNamePropertyInfo = "property-name"
type AttrOrigin PropertyActionPropertyNamePropertyInfo = PropertyAction
attrGet = undefined
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructPropertyActionPropertyName
attrClear = undefined
#endif
getPropertyActionState :: (MonadIO m, IsPropertyAction o) => o -> m (Maybe GVariant)
getPropertyActionState :: o -> m (Maybe GVariant)
getPropertyActionState obj :: o
obj = IO (Maybe GVariant) -> m (Maybe GVariant)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe GVariant) -> m (Maybe GVariant))
-> IO (Maybe GVariant) -> m (Maybe GVariant)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe GVariant)
forall a. GObject a => a -> String -> IO (Maybe GVariant)
B.Properties.getObjectPropertyVariant o
obj "state"
#if defined(ENABLE_OVERLOADING)
data PropertyActionStatePropertyInfo
instance AttrInfo PropertyActionStatePropertyInfo where
type AttrAllowedOps PropertyActionStatePropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint PropertyActionStatePropertyInfo = IsPropertyAction
type AttrSetTypeConstraint PropertyActionStatePropertyInfo = (~) ()
type AttrTransferTypeConstraint PropertyActionStatePropertyInfo = (~) ()
type AttrTransferType PropertyActionStatePropertyInfo = ()
type AttrGetType PropertyActionStatePropertyInfo = (Maybe GVariant)
type AttrLabel PropertyActionStatePropertyInfo = "state"
type AttrOrigin PropertyActionStatePropertyInfo = PropertyAction
attrGet = getPropertyActionState
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
#endif
getPropertyActionStateType :: (MonadIO m, IsPropertyAction o) => o -> m (Maybe GLib.VariantType.VariantType)
getPropertyActionStateType :: o -> m (Maybe VariantType)
getPropertyActionStateType obj :: o
obj = IO (Maybe VariantType) -> m (Maybe VariantType)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe VariantType) -> m (Maybe VariantType))
-> IO (Maybe VariantType) -> m (Maybe VariantType)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr VariantType -> VariantType)
-> IO (Maybe VariantType)
forall a b.
(GObject a, BoxedObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj "state-type" ManagedPtr VariantType -> VariantType
GLib.VariantType.VariantType
#if defined(ENABLE_OVERLOADING)
data PropertyActionStateTypePropertyInfo
instance AttrInfo PropertyActionStateTypePropertyInfo where
type AttrAllowedOps PropertyActionStateTypePropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint PropertyActionStateTypePropertyInfo = IsPropertyAction
type AttrSetTypeConstraint PropertyActionStateTypePropertyInfo = (~) ()
type AttrTransferTypeConstraint PropertyActionStateTypePropertyInfo = (~) ()
type AttrTransferType PropertyActionStateTypePropertyInfo = ()
type AttrGetType PropertyActionStateTypePropertyInfo = (Maybe GLib.VariantType.VariantType)
type AttrLabel PropertyActionStateTypePropertyInfo = "state-type"
type AttrOrigin PropertyActionStateTypePropertyInfo = PropertyAction
attrGet = getPropertyActionStateType
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList PropertyAction
type instance O.AttributeList PropertyAction = PropertyActionAttributeList
type PropertyActionAttributeList = ('[ '("enabled", PropertyActionEnabledPropertyInfo), '("invertBoolean", PropertyActionInvertBooleanPropertyInfo), '("name", PropertyActionNamePropertyInfo), '("object", PropertyActionObjectPropertyInfo), '("parameterType", PropertyActionParameterTypePropertyInfo), '("propertyName", PropertyActionPropertyNamePropertyInfo), '("state", PropertyActionStatePropertyInfo), '("stateType", PropertyActionStateTypePropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
propertyActionEnabled :: AttrLabelProxy "enabled"
propertyActionEnabled = AttrLabelProxy
propertyActionInvertBoolean :: AttrLabelProxy "invertBoolean"
propertyActionInvertBoolean = AttrLabelProxy
propertyActionName :: AttrLabelProxy "name"
propertyActionName = AttrLabelProxy
propertyActionObject :: AttrLabelProxy "object"
propertyActionObject = AttrLabelProxy
propertyActionParameterType :: AttrLabelProxy "parameterType"
propertyActionParameterType = AttrLabelProxy
propertyActionPropertyName :: AttrLabelProxy "propertyName"
propertyActionPropertyName = AttrLabelProxy
propertyActionState :: AttrLabelProxy "state"
propertyActionState = AttrLabelProxy
propertyActionStateType :: AttrLabelProxy "stateType"
propertyActionStateType = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList PropertyAction = PropertyActionSignalList
type PropertyActionSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_property_action_new" g_property_action_new ::
CString ->
Ptr GObject.Object.Object ->
CString ->
IO (Ptr PropertyAction)
propertyActionNew ::
(B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a) =>
T.Text
-> a
-> T.Text
-> m PropertyAction
propertyActionNew :: Text -> a -> Text -> m PropertyAction
propertyActionNew name :: Text
name object :: a
object propertyName :: Text
propertyName = IO PropertyAction -> m PropertyAction
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PropertyAction -> m PropertyAction)
-> IO PropertyAction -> m PropertyAction
forall a b. (a -> b) -> a -> b
$ do
CString
name' <- Text -> IO CString
textToCString Text
name
Ptr Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
CString
propertyName' <- Text -> IO CString
textToCString Text
propertyName
Ptr PropertyAction
result <- CString -> Ptr Object -> CString -> IO (Ptr PropertyAction)
g_property_action_new CString
name' Ptr Object
object' CString
propertyName'
Text -> Ptr PropertyAction -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "propertyActionNew" Ptr PropertyAction
result
PropertyAction
result' <- ((ManagedPtr PropertyAction -> PropertyAction)
-> Ptr PropertyAction -> IO PropertyAction
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr PropertyAction -> PropertyAction
PropertyAction) Ptr PropertyAction
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
propertyName'
PropertyAction -> IO PropertyAction
forall (m :: * -> *) a. Monad m => a -> m a
return PropertyAction
result'
#if defined(ENABLE_OVERLOADING)
#endif