{-# 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 ,
#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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
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 qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
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
#else
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
#endif
newtype PropertyAction = PropertyAction (SP.ManagedPtr PropertyAction)
deriving (PropertyAction -> PropertyAction -> Bool
(PropertyAction -> PropertyAction -> Bool)
-> (PropertyAction -> PropertyAction -> Bool) -> Eq PropertyAction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PropertyAction -> PropertyAction -> Bool
== :: PropertyAction -> PropertyAction -> Bool
$c/= :: PropertyAction -> PropertyAction -> Bool
/= :: PropertyAction -> PropertyAction -> Bool
Eq)
instance SP.ManagedPtrNewtype PropertyAction where
toManagedPtr :: PropertyAction -> ManagedPtr PropertyAction
toManagedPtr (PropertyAction ManagedPtr PropertyAction
p) = ManagedPtr PropertyAction
p
foreign import ccall "g_property_action_get_type"
c_g_property_action_get_type :: IO B.Types.GType
instance B.Types.TypedObject PropertyAction where
glibType :: IO GType
glibType = IO GType
c_g_property_action_get_type
instance B.Types.GObject PropertyAction
class (SP.GObject o, O.IsDescendantOf PropertyAction o) => IsPropertyAction o
instance (SP.GObject o, O.IsDescendantOf PropertyAction o) => IsPropertyAction o
instance O.HasParentTypes PropertyAction
type instance O.ParentTypes PropertyAction = '[GObject.Object.Object, Gio.Action.Action]
toPropertyAction :: (MIO.MonadIO m, IsPropertyAction o) => o -> m PropertyAction
toPropertyAction :: forall (m :: * -> *) o.
(MonadIO m, IsPropertyAction o) =>
o -> m PropertyAction
toPropertyAction = IO PropertyAction -> m PropertyAction
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr PropertyAction -> PropertyAction
PropertyAction
instance B.GValue.IsGValue (Maybe PropertyAction) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_property_action_get_type
gvalueSet_ :: Ptr GValue -> Maybe PropertyAction -> IO ()
gvalueSet_ Ptr GValue
gv Maybe PropertyAction
P.Nothing = Ptr GValue -> Ptr PropertyAction -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr PropertyAction
forall a. Ptr a
FP.nullPtr :: FP.Ptr PropertyAction)
gvalueSet_ Ptr GValue
gv (P.Just PropertyAction
obj) = PropertyAction -> (Ptr PropertyAction -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr PropertyAction
obj (Ptr GValue -> Ptr PropertyAction -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe PropertyAction)
gvalueGet_ Ptr GValue
gv = do
ptr <- Ptr GValue -> IO (Ptr PropertyAction)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr PropertyAction)
if ptr /= FP.nullPtr
then P.Just <$> B.ManagedPtr.newObject PropertyAction ptr
else return P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolvePropertyActionMethod (t :: Symbol) (o :: DK.Type) :: DK.Type 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.OverloadedMethod info PropertyAction p) => OL.IsLabel t (PropertyAction -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel :: PropertyAction -> p
fromLabel = forall {k} (i :: k) o s. OverloadedMethod i o s => o -> s
forall i o s. OverloadedMethod i o s => o -> s
O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolvePropertyActionMethod t PropertyAction, O.OverloadedMethod info PropertyAction p, R.HasField t PropertyAction p) => R.HasField t PropertyAction p where
getField :: PropertyAction -> p
getField = forall {k} (i :: k) o s. OverloadedMethod i o s => o -> s
forall i o s. OverloadedMethod i o s => o -> s
O.overloadedMethod @info
#endif
instance (info ~ ResolvePropertyActionMethod t PropertyAction, O.OverloadedMethodInfo info PropertyAction) => OL.IsLabel t (O.MethodProxy info PropertyAction) where
#if MIN_VERSION_base(4,10,0)
fromLabel :: MethodProxy info PropertyAction
fromLabel = MethodProxy info PropertyAction
forall info obj. MethodProxy info obj
O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
getPropertyActionEnabled :: (MonadIO m, IsPropertyAction o) => o -> m Bool
getPropertyActionEnabled :: forall (m :: * -> *) o.
(MonadIO m, IsPropertyAction o) =>
o -> m Bool
getPropertyActionEnabled o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"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 :: forall o.
AttrBaseTypeConstraint PropertyActionEnabledPropertyInfo o =>
o -> IO (AttrGetType PropertyActionEnabledPropertyInfo)
attrGet = o -> IO Bool
o -> IO (AttrGetType PropertyActionEnabledPropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsPropertyAction o) =>
o -> m Bool
getPropertyActionEnabled
attrSet :: forall o b.
(AttrBaseTypeConstraint PropertyActionEnabledPropertyInfo o,
AttrSetTypeConstraint PropertyActionEnabledPropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint PropertyActionEnabledPropertyInfo o,
AttrTransferTypeConstraint PropertyActionEnabledPropertyInfo b) =>
Proxy o
-> b -> IO (AttrTransferType PropertyActionEnabledPropertyInfo)
attrTransfer Proxy o
_ = b -> IO (AttrTransferType PropertyActionEnabledPropertyInfo)
() -> IO ()
forall a. HasCallStack => a
undefined
attrConstruct :: forall o b.
(AttrBaseTypeConstraint PropertyActionEnabledPropertyInfo o,
AttrSetTypeConstraint PropertyActionEnabledPropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
forall a. HasCallStack => a
undefined
attrClear :: forall o.
AttrBaseTypeConstraint PropertyActionEnabledPropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Objects.PropertyAction.enabled"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Objects-PropertyAction.html#g:attr:enabled"
})
#endif
getPropertyActionInvertBoolean :: (MonadIO m, IsPropertyAction o) => o -> m Bool
getPropertyActionInvertBoolean :: forall (m :: * -> *) o.
(MonadIO m, IsPropertyAction o) =>
o -> m Bool
getPropertyActionInvertBoolean o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"invert-boolean"
constructPropertyActionInvertBoolean :: (IsPropertyAction o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructPropertyActionInvertBoolean :: forall o (m :: * -> *).
(IsPropertyAction o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructPropertyActionInvertBoolean Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"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 :: forall o.
AttrBaseTypeConstraint PropertyActionInvertBooleanPropertyInfo o =>
o -> IO (AttrGetType PropertyActionInvertBooleanPropertyInfo)
attrGet = o -> IO Bool
o -> IO (AttrGetType PropertyActionInvertBooleanPropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsPropertyAction o) =>
o -> m Bool
getPropertyActionInvertBoolean
attrSet :: forall o b.
(AttrBaseTypeConstraint PropertyActionInvertBooleanPropertyInfo o,
AttrSetTypeConstraint PropertyActionInvertBooleanPropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint PropertyActionInvertBooleanPropertyInfo o,
AttrTransferTypeConstraint
PropertyActionInvertBooleanPropertyInfo b) =>
Proxy o
-> b
-> IO (AttrTransferType PropertyActionInvertBooleanPropertyInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
attrConstruct :: forall o b.
(AttrBaseTypeConstraint PropertyActionInvertBooleanPropertyInfo o,
AttrSetTypeConstraint PropertyActionInvertBooleanPropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
Bool -> IO (GValueConstruct o)
forall o (m :: * -> *).
(IsPropertyAction o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructPropertyActionInvertBoolean
attrClear :: forall o.
AttrBaseTypeConstraint PropertyActionInvertBooleanPropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Objects.PropertyAction.invertBoolean"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Objects-PropertyAction.html#g:attr:invertBoolean"
})
#endif
getPropertyActionName :: (MonadIO m, IsPropertyAction o) => o -> m (Maybe T.Text)
getPropertyActionName :: forall (m :: * -> *) o.
(MonadIO m, IsPropertyAction o) =>
o -> m (Maybe Text)
getPropertyActionName o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"name"
constructPropertyActionName :: (IsPropertyAction o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructPropertyActionName :: forall o (m :: * -> *).
(IsPropertyAction o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructPropertyActionName Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"name" (Text -> Maybe Text
forall a. a -> Maybe a
P.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 :: forall o.
AttrBaseTypeConstraint PropertyActionNamePropertyInfo o =>
o -> IO (AttrGetType PropertyActionNamePropertyInfo)
attrGet = o -> IO (Maybe Text)
o -> IO (AttrGetType PropertyActionNamePropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsPropertyAction o) =>
o -> m (Maybe Text)
getPropertyActionName
attrSet :: forall o b.
(AttrBaseTypeConstraint PropertyActionNamePropertyInfo o,
AttrSetTypeConstraint PropertyActionNamePropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint PropertyActionNamePropertyInfo o,
AttrTransferTypeConstraint PropertyActionNamePropertyInfo b) =>
Proxy o
-> b -> IO (AttrTransferType PropertyActionNamePropertyInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
attrConstruct :: forall o b.
(AttrBaseTypeConstraint PropertyActionNamePropertyInfo o,
AttrSetTypeConstraint PropertyActionNamePropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
Text -> IO (GValueConstruct o)
forall o (m :: * -> *).
(IsPropertyAction o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructPropertyActionName
attrClear :: forall o.
AttrBaseTypeConstraint PropertyActionNamePropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Objects.PropertyAction.name"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Objects-PropertyAction.html#g:attr:name"
})
#endif
constructPropertyActionObject :: (IsPropertyAction o, MIO.MonadIO m, GObject.Object.IsObject a) => a -> m (GValueConstruct o)
constructPropertyActionObject :: forall o (m :: * -> *) a.
(IsPropertyAction o, MonadIO m, IsObject a) =>
a -> m (GValueConstruct o)
constructPropertyActionObject a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"object" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data 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 :: forall o.
AttrBaseTypeConstraint PropertyActionObjectPropertyInfo o =>
o -> IO (AttrGetType PropertyActionObjectPropertyInfo)
attrGet = o -> IO ()
o -> IO (AttrGetType PropertyActionObjectPropertyInfo)
forall a. HasCallStack => a
undefined
attrSet :: forall o b.
(AttrBaseTypeConstraint PropertyActionObjectPropertyInfo o,
AttrSetTypeConstraint PropertyActionObjectPropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint PropertyActionObjectPropertyInfo o,
AttrTransferTypeConstraint PropertyActionObjectPropertyInfo b) =>
Proxy o
-> b -> IO (AttrTransferType PropertyActionObjectPropertyInfo)
attrTransfer Proxy o
_ b
v = do
(ManagedPtr Object -> Object) -> b -> IO Object
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Object -> Object
GObject.Object.Object b
v
attrConstruct :: forall o b.
(AttrBaseTypeConstraint PropertyActionObjectPropertyInfo o,
AttrSetTypeConstraint PropertyActionObjectPropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
forall o (m :: * -> *) a.
(IsPropertyAction o, MonadIO m, IsObject a) =>
a -> m (GValueConstruct o)
constructPropertyActionObject
attrClear :: forall o.
AttrBaseTypeConstraint PropertyActionObjectPropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Objects.PropertyAction.object"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Objects-PropertyAction.html#g:attr:object"
})
#endif
getPropertyActionParameterType :: (MonadIO m, IsPropertyAction o) => o -> m (Maybe GLib.VariantType.VariantType)
getPropertyActionParameterType :: forall (m :: * -> *) o.
(MonadIO m, IsPropertyAction o) =>
o -> m (Maybe VariantType)
getPropertyActionParameterType o
obj = IO (Maybe VariantType) -> m (Maybe VariantType)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj String
"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 :: forall o.
AttrBaseTypeConstraint PropertyActionParameterTypePropertyInfo o =>
o -> IO (AttrGetType PropertyActionParameterTypePropertyInfo)
attrGet = o -> IO (Maybe VariantType)
o -> IO (AttrGetType PropertyActionParameterTypePropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsPropertyAction o) =>
o -> m (Maybe VariantType)
getPropertyActionParameterType
attrSet :: forall o b.
(AttrBaseTypeConstraint PropertyActionParameterTypePropertyInfo o,
AttrSetTypeConstraint PropertyActionParameterTypePropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint PropertyActionParameterTypePropertyInfo o,
AttrTransferTypeConstraint
PropertyActionParameterTypePropertyInfo b) =>
Proxy o
-> b
-> IO (AttrTransferType PropertyActionParameterTypePropertyInfo)
attrTransfer Proxy o
_ = b -> IO (AttrTransferType PropertyActionParameterTypePropertyInfo)
() -> IO ()
forall a. HasCallStack => a
undefined
attrConstruct :: forall o b.
(AttrBaseTypeConstraint PropertyActionParameterTypePropertyInfo o,
AttrSetTypeConstraint PropertyActionParameterTypePropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
forall a. HasCallStack => a
undefined
attrClear :: forall o.
AttrBaseTypeConstraint PropertyActionParameterTypePropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Objects.PropertyAction.parameterType"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Objects-PropertyAction.html#g:attr:parameterType"
})
#endif
constructPropertyActionPropertyName :: (IsPropertyAction o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructPropertyActionPropertyName :: forall o (m :: * -> *).
(IsPropertyAction o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructPropertyActionPropertyName Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"property-name" (Text -> Maybe Text
forall a. a -> Maybe a
P.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 :: forall o.
AttrBaseTypeConstraint PropertyActionPropertyNamePropertyInfo o =>
o -> IO (AttrGetType PropertyActionPropertyNamePropertyInfo)
attrGet = o -> IO ()
o -> IO (AttrGetType PropertyActionPropertyNamePropertyInfo)
forall a. HasCallStack => a
undefined
attrSet :: forall o b.
(AttrBaseTypeConstraint PropertyActionPropertyNamePropertyInfo o,
AttrSetTypeConstraint PropertyActionPropertyNamePropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint PropertyActionPropertyNamePropertyInfo o,
AttrTransferTypeConstraint
PropertyActionPropertyNamePropertyInfo b) =>
Proxy o
-> b
-> IO (AttrTransferType PropertyActionPropertyNamePropertyInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
attrConstruct :: forall o b.
(AttrBaseTypeConstraint PropertyActionPropertyNamePropertyInfo o,
AttrSetTypeConstraint PropertyActionPropertyNamePropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
Text -> IO (GValueConstruct o)
forall o (m :: * -> *).
(IsPropertyAction o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructPropertyActionPropertyName
attrClear :: forall o.
AttrBaseTypeConstraint PropertyActionPropertyNamePropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Objects.PropertyAction.propertyName"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Objects-PropertyAction.html#g:attr:propertyName"
})
#endif
getPropertyActionState :: (MonadIO m, IsPropertyAction o) => o -> m (Maybe GVariant)
getPropertyActionState :: forall (m :: * -> *) o.
(MonadIO m, IsPropertyAction o) =>
o -> m (Maybe GVariant)
getPropertyActionState o
obj = IO (Maybe GVariant) -> m (Maybe GVariant)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"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 :: forall o.
AttrBaseTypeConstraint PropertyActionStatePropertyInfo o =>
o -> IO (AttrGetType PropertyActionStatePropertyInfo)
attrGet = o -> IO (Maybe GVariant)
o -> IO (AttrGetType PropertyActionStatePropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsPropertyAction o) =>
o -> m (Maybe GVariant)
getPropertyActionState
attrSet :: forall o b.
(AttrBaseTypeConstraint PropertyActionStatePropertyInfo o,
AttrSetTypeConstraint PropertyActionStatePropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint PropertyActionStatePropertyInfo o,
AttrTransferTypeConstraint PropertyActionStatePropertyInfo b) =>
Proxy o
-> b -> IO (AttrTransferType PropertyActionStatePropertyInfo)
attrTransfer Proxy o
_ = b -> IO (AttrTransferType PropertyActionStatePropertyInfo)
() -> IO ()
forall a. HasCallStack => a
undefined
attrConstruct :: forall o b.
(AttrBaseTypeConstraint PropertyActionStatePropertyInfo o,
AttrSetTypeConstraint PropertyActionStatePropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
forall a. HasCallStack => a
undefined
attrClear :: forall o.
AttrBaseTypeConstraint PropertyActionStatePropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Objects.PropertyAction.state"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Objects-PropertyAction.html#g:attr:state"
})
#endif
getPropertyActionStateType :: (MonadIO m, IsPropertyAction o) => o -> m (Maybe GLib.VariantType.VariantType)
getPropertyActionStateType :: forall (m :: * -> *) o.
(MonadIO m, IsPropertyAction o) =>
o -> m (Maybe VariantType)
getPropertyActionStateType o
obj = IO (Maybe VariantType) -> m (Maybe VariantType)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj String
"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 :: forall o.
AttrBaseTypeConstraint PropertyActionStateTypePropertyInfo o =>
o -> IO (AttrGetType PropertyActionStateTypePropertyInfo)
attrGet = o -> IO (Maybe VariantType)
o -> IO (AttrGetType PropertyActionStateTypePropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsPropertyAction o) =>
o -> m (Maybe VariantType)
getPropertyActionStateType
attrSet :: forall o b.
(AttrBaseTypeConstraint PropertyActionStateTypePropertyInfo o,
AttrSetTypeConstraint PropertyActionStateTypePropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint PropertyActionStateTypePropertyInfo o,
AttrTransferTypeConstraint
PropertyActionStateTypePropertyInfo b) =>
Proxy o
-> b -> IO (AttrTransferType PropertyActionStateTypePropertyInfo)
attrTransfer Proxy o
_ = b -> IO (AttrTransferType PropertyActionStateTypePropertyInfo)
() -> IO ()
forall a. HasCallStack => a
undefined
attrConstruct :: forall o b.
(AttrBaseTypeConstraint PropertyActionStateTypePropertyInfo o,
AttrSetTypeConstraint PropertyActionStateTypePropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
forall a. HasCallStack => a
undefined
attrClear :: forall o.
AttrBaseTypeConstraint PropertyActionStateTypePropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Objects.PropertyAction.stateType"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Objects-PropertyAction.html#g:attr:stateType"
})
#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, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
propertyActionEnabled :: AttrLabelProxy "enabled"
propertyActionEnabled :: AttrLabelProxy "enabled"
propertyActionEnabled = AttrLabelProxy "enabled"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
propertyActionInvertBoolean :: AttrLabelProxy "invertBoolean"
propertyActionInvertBoolean :: AttrLabelProxy "invertBoolean"
propertyActionInvertBoolean = AttrLabelProxy "invertBoolean"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
propertyActionName :: AttrLabelProxy "name"
propertyActionName :: AttrLabelProxy "name"
propertyActionName = AttrLabelProxy "name"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
propertyActionObject :: AttrLabelProxy "object"
propertyActionObject :: AttrLabelProxy "object"
propertyActionObject = AttrLabelProxy "object"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
propertyActionParameterType :: AttrLabelProxy "parameterType"
propertyActionParameterType :: AttrLabelProxy "parameterType"
propertyActionParameterType = AttrLabelProxy "parameterType"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
propertyActionPropertyName :: AttrLabelProxy "propertyName"
propertyActionPropertyName :: AttrLabelProxy "propertyName"
propertyActionPropertyName = AttrLabelProxy "propertyName"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
propertyActionState :: AttrLabelProxy "state"
propertyActionState :: AttrLabelProxy "state"
propertyActionState = AttrLabelProxy "state"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
propertyActionStateType :: AttrLabelProxy "stateType"
propertyActionStateType :: AttrLabelProxy "stateType"
propertyActionStateType = AttrLabelProxy "stateType"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList PropertyAction = PropertyActionSignalList
type PropertyActionSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
Text -> a -> Text -> m PropertyAction
propertyActionNew Text
name a
object Text
propertyName = IO PropertyAction -> m PropertyAction
forall a. IO a -> m a
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
name' <- Text -> IO CString
textToCString Text
name
object' <- unsafeManagedPtrCastPtr object
propertyName' <- textToCString propertyName
result <- g_property_action_new name' object' propertyName'
checkUnexpectedReturnNULL "propertyActionNew" result
result' <- (wrapObject PropertyAction) result
touchManagedPtr object
freeMem name'
freeMem propertyName'
return result'
#if defined(ENABLE_OVERLOADING)
#endif