{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A t'GI.Gio.Objects.PropertyAction.PropertyAction' is a way to get a t'GI.Gio.Interfaces.Action.Action' with a state value
-- reflecting and controlling the value of a t'GI.GObject.Objects.Object.Object' property.
-- 
-- The state of the action will correspond to the value of the property.
-- Changing it will change the property (assuming the requested value
-- matches the requirements as specified in the t'GI.GObject.Objects.ParamSpec.ParamSpec').
-- 
-- Only the most common types are presently supported.  Booleans are
-- mapped to booleans, strings to strings, signed\/unsigned integers to
-- int32\/uint32 and floats and doubles to doubles.
-- 
-- If the property is an enum then the state will be string-typed and
-- conversion will automatically be performed between the enum value and
-- \"nick\" string as per the t'GI.GObject.Structs.EnumValue.EnumValue' table.
-- 
-- Flags types are not currently supported.
-- 
-- Properties of object types, boxed types and pointer types are not
-- supported and probably never will be.
-- 
-- Properties of t'GVariant' types are not currently supported.
-- 
-- If the property is boolean-valued then the action will have a NULL
-- parameter type, and activating the action (with no parameter) will
-- toggle the value of the property.
-- 
-- In all other cases, the parameter type will correspond to the type of
-- the property.
-- 
-- The general idea here is to reduce the number of locations where a
-- particular piece of state is kept (and therefore has to be synchronised
-- between). t'GI.Gio.Objects.PropertyAction.PropertyAction' does not have a separate state that is kept
-- in sync with the property value -- its state is the property value.
-- 
-- For example, it might be useful to create a t'GI.Gio.Interfaces.Action.Action' corresponding to
-- the \"visible-child-name\" property of a @/GtkStack/@ so that the current
-- page can be switched from a menu.  The active radio indication in the
-- menu is then directly determined from the active page of the
-- @/GtkStack/@.
-- 
-- An anti-example would be binding the \"active-id\" property on a
-- @/GtkComboBox/@.  This is because the state of the combobox itself is
-- probably uninteresting and is actually being used to control
-- something else.
-- 
-- Another anti-example would be to bind to the \"visible-child-name\"
-- property of a @/GtkStack/@ if this value is actually stored in
-- t'GI.Gio.Objects.Settings.Settings'.  In that case, the real source of the value is
-- t'GI.Gio.Objects.Settings.Settings'.  If you want a t'GI.Gio.Interfaces.Action.Action' to control a setting stored in
-- t'GI.Gio.Objects.Settings.Settings', see 'GI.Gio.Objects.Settings.settingsCreateAction' instead, and possibly
-- combine its use with 'GI.Gio.Objects.Settings.settingsBind'.
-- 
-- /Since: 2.38/

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

module GI.Gio.Objects.PropertyAction
    ( 

-- * Exported types
    PropertyAction(..)                      ,
    IsPropertyAction                        ,
    toPropertyAction                        ,
    noPropertyAction                        ,


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

#if defined(ENABLE_OVERLOADING)
    ResolvePropertyActionMethod             ,
#endif


-- ** new #method:new#

    propertyActionNew                       ,




 -- * Properties
-- ** enabled #attr:enabled#
-- | If /@action@/ is currently enabled.
-- 
-- If the action is disabled then calls to 'GI.Gio.Interfaces.Action.actionActivate' and
-- 'GI.Gio.Interfaces.Action.actionChangeState' have no effect.
-- 
-- /Since: 2.38/

#if defined(ENABLE_OVERLOADING)
    PropertyActionEnabledPropertyInfo       ,
#endif
    getPropertyActionEnabled                ,
#if defined(ENABLE_OVERLOADING)
    propertyActionEnabled                   ,
#endif


-- ** invertBoolean #attr:invertBoolean#
-- | If 'P.True', the state of the action will be the negation of the
-- property value, provided the property is boolean.
-- 
-- /Since: 2.46/

#if defined(ENABLE_OVERLOADING)
    PropertyActionInvertBooleanPropertyInfo ,
#endif
    constructPropertyActionInvertBoolean    ,
    getPropertyActionInvertBoolean          ,
#if defined(ENABLE_OVERLOADING)
    propertyActionInvertBoolean             ,
#endif


-- ** name #attr:name#
-- | The name of the action.  This is mostly meaningful for identifying
-- the action once it has been added to a t'GI.Gio.Interfaces.ActionMap.ActionMap'.
-- 
-- /Since: 2.38/

#if defined(ENABLE_OVERLOADING)
    PropertyActionNamePropertyInfo          ,
#endif
    constructPropertyActionName             ,
    getPropertyActionName                   ,
#if defined(ENABLE_OVERLOADING)
    propertyActionName                      ,
#endif


-- ** object #attr:object#
-- | The object to wrap a property on.
-- 
-- The object must be a non-'P.Nothing' t'GI.GObject.Objects.Object.Object' with properties.
-- 
-- /Since: 2.38/

#if defined(ENABLE_OVERLOADING)
    PropertyActionObjectPropertyInfo        ,
#endif
    constructPropertyActionObject           ,
#if defined(ENABLE_OVERLOADING)
    propertyActionObject                    ,
#endif


-- ** parameterType #attr:parameterType#
-- | The type of the parameter that must be given when activating the
-- action.
-- 
-- /Since: 2.38/

#if defined(ENABLE_OVERLOADING)
    PropertyActionParameterTypePropertyInfo ,
#endif
    getPropertyActionParameterType          ,
#if defined(ENABLE_OVERLOADING)
    propertyActionParameterType             ,
#endif


-- ** propertyName #attr:propertyName#
-- | The name of the property to wrap on the object.
-- 
-- The property must exist on the passed-in object and it must be
-- readable and writable (and not construct-only).
-- 
-- /Since: 2.38/

#if defined(ENABLE_OVERLOADING)
    PropertyActionPropertyNamePropertyInfo  ,
#endif
    constructPropertyActionPropertyName     ,
#if defined(ENABLE_OVERLOADING)
    propertyActionPropertyName              ,
#endif


-- ** state #attr:state#
-- | The state of the action, or 'P.Nothing' if the action is stateless.
-- 
-- /Since: 2.38/

#if defined(ENABLE_OVERLOADING)
    PropertyActionStatePropertyInfo         ,
#endif
    getPropertyActionState                  ,
#if defined(ENABLE_OVERLOADING)
    propertyActionState                     ,
#endif


-- ** stateType #attr:stateType#
-- | The t'GI.GLib.Structs.VariantType.VariantType' of the state that the action has, or 'P.Nothing' if the
-- action is stateless.
-- 
-- /Since: 2.38/

#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 Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified 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

-- | Memory-managed wrapper type.
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
    

-- | Convert 'PropertyAction' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
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
        
    

-- | Type class for types which can be safely cast to `PropertyAction`, for instance with `toPropertyAction`.
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]

-- | Cast to `PropertyAction`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
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

-- | A convenience alias for `Nothing` :: `Maybe` `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

--- XXX Duplicated object with different types:
  --- Name {namespace = "Gio", name = "PropertyAction"} -> Property {propName = "enabled", propType = TBasicType TBoolean, propFlags = [PropertyReadable], propReadNullable = Nothing, propWriteNullable = Nothing, propTransfer = TransferNothing, propDoc = Documentation {rawDocText = Just "If @action is currently enabled.\n\nIf the action is disabled then calls to g_action_activate() and\ng_action_change_state() have no effect.", sinceVersion = Just "2.38"}, propDeprecated = Nothing}
  --- Name {namespace = "Gio", name = "Action"} -> Property {propName = "enabled", propType = TBasicType TBoolean, propFlags = [PropertyReadable], propReadNullable = Nothing, propWriteNullable = Nothing, propTransfer = TransferNothing, propDoc = Documentation {rawDocText = Just "If @action is currently enabled.\n\nIf the action is disabled then calls to g_action_activate() and\ng_action_change_state() have no effect.", sinceVersion = Just "2.28"}, propDeprecated = Nothing}
--- XXX Duplicated object with different types:
  --- Name {namespace = "Gio", name = "PropertyAction"} -> Property {propName = "name", propType = TBasicType TUTF8, propFlags = [PropertyReadable,PropertyWritable,PropertyConstructOnly], propReadNullable = Nothing, propWriteNullable = Nothing, propTransfer = TransferNothing, propDoc = Documentation {rawDocText = Just "The name of the action.  This is mostly meaningful for identifying\nthe action once it has been added to a #GActionMap.", sinceVersion = Just "2.38"}, propDeprecated = Nothing}
  --- Name {namespace = "Gio", name = "Action"} -> Property {propName = "name", propType = TBasicType TUTF8, propFlags = [PropertyReadable], propReadNullable = Nothing, propWriteNullable = Nothing, propTransfer = TransferNothing, propDoc = Documentation {rawDocText = Just "The name of the action.  This is mostly meaningful for identifying\nthe action once it has been added to a #GActionGroup. It is immutable.", sinceVersion = Just "2.28"}, propDeprecated = Nothing}
--- XXX Duplicated object with different types:
  --- Name {namespace = "Gio", name = "PropertyAction"} -> Property {propName = "parameter-type", propType = TInterface (Name {namespace = "GLib", name = "VariantType"}), propFlags = [PropertyReadable], propReadNullable = Nothing, propWriteNullable = Nothing, propTransfer = TransferNothing, propDoc = Documentation {rawDocText = Just "The type of the parameter that must be given when activating the\naction.", sinceVersion = Just "2.38"}, propDeprecated = Nothing}
  --- Name {namespace = "Gio", name = "Action"} -> Property {propName = "parameter-type", propType = TInterface (Name {namespace = "GLib", name = "VariantType"}), propFlags = [PropertyReadable], propReadNullable = Nothing, propWriteNullable = Nothing, propTransfer = TransferNothing, propDoc = Documentation {rawDocText = Just "The type of the parameter that must be given when activating the\naction. This is immutable, and may be %NULL if no parameter is needed when\nactivating the action.", sinceVersion = Just "2.28"}, propDeprecated = Nothing}
--- XXX Duplicated object with different types:
  --- Name {namespace = "Gio", name = "PropertyAction"} -> Property {propName = "state", propType = TVariant, propFlags = [PropertyReadable], propReadNullable = Nothing, propWriteNullable = Nothing, propTransfer = TransferNothing, propDoc = Documentation {rawDocText = Just "The state of the action, or %NULL if the action is stateless.", sinceVersion = Just "2.38"}, propDeprecated = Nothing}
  --- Name {namespace = "Gio", name = "Action"} -> Property {propName = "state", propType = TVariant, propFlags = [PropertyReadable], propReadNullable = Nothing, propWriteNullable = Nothing, propTransfer = TransferNothing, propDoc = Documentation {rawDocText = Just "The state of the action, or %NULL if the action is stateless.", sinceVersion = Just "2.28"}, propDeprecated = Nothing}
--- XXX Duplicated object with different types:
  --- Name {namespace = "Gio", name = "PropertyAction"} -> Property {propName = "state-type", propType = TInterface (Name {namespace = "GLib", name = "VariantType"}), propFlags = [PropertyReadable], propReadNullable = Nothing, propWriteNullable = Nothing, propTransfer = TransferNothing, propDoc = Documentation {rawDocText = Just "The #GVariantType of the state that the action has, or %NULL if the\naction is stateless.", sinceVersion = Just "2.38"}, propDeprecated = Nothing}
  --- Name {namespace = "Gio", name = "Action"} -> Property {propName = "state-type", propType = TInterface (Name {namespace = "GLib", name = "VariantType"}), propFlags = [PropertyReadable], propReadNullable = Nothing, propWriteNullable = Nothing, propTransfer = TransferNothing, propDoc = Documentation {rawDocText = Just "The #GVariantType of the state that the action has, or %NULL if the\naction is stateless. This is immutable.", sinceVersion = Just "2.28"}, propDeprecated = Nothing}
-- VVV Prop "enabled"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@enabled@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' propertyAction #enabled
-- @
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

-- VVV Prop "invert-boolean"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@invert-boolean@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' propertyAction #invertBoolean
-- @
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"

-- | Construct a `GValueConstruct` with valid value for the “@invert-boolean@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPropertyActionInvertBoolean :: (IsPropertyAction o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructPropertyActionInvertBoolean :: Bool -> m (GValueConstruct o)
constructPropertyActionInvertBoolean val :: Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ 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

-- VVV Prop "name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' propertyAction #name
-- @
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"

-- | Construct a `GValueConstruct` with valid value for the “@name@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPropertyActionName :: (IsPropertyAction o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructPropertyActionName :: Text -> m (GValueConstruct o)
constructPropertyActionName val :: Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ 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
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 = getPropertyActionName
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructPropertyActionName
    attrClear = undefined
#endif

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

-- | Construct a `GValueConstruct` with valid value for the “@object@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPropertyActionObject :: (IsPropertyAction o, MIO.MonadIO m, GObject.Object.IsObject a) => a -> m (GValueConstruct o)
constructPropertyActionObject :: a -> m (GValueConstruct o)
constructPropertyActionObject val :: a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ 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
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 = undefined
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo GObject.Object.Object v
    attrConstruct = constructPropertyActionObject
    attrClear = undefined
#endif

-- VVV Prop "parameter-type"
   -- Type: TInterface (Name {namespace = "GLib", name = "VariantType"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@parameter-type@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' propertyAction #parameterType
-- @
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

-- VVV Prop "property-name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Construct a `GValueConstruct` with valid value for the “@property-name@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPropertyActionPropertyName :: (IsPropertyAction o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructPropertyActionPropertyName :: Text -> m (GValueConstruct o)
constructPropertyActionPropertyName val :: Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ 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
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 = undefined
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructPropertyActionPropertyName
    attrClear = undefined
#endif

-- VVV Prop "state"
   -- Type: TVariant
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@state@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' propertyAction #state
-- @
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

-- VVV Prop "state-type"
   -- Type: TInterface (Name {namespace = "GLib", name = "VariantType"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@state-type@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' propertyAction #stateType
-- @
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

-- method PropertyAction::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the action to create"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "object"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the object that has the property\n  to wrap"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the property"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "PropertyAction" })
-- throws : False
-- Skip return : False

foreign import ccall "g_property_action_new" g_property_action_new :: 
    CString ->                              -- name : TBasicType TUTF8
    Ptr GObject.Object.Object ->            -- object : TInterface (Name {namespace = "GObject", name = "Object"})
    CString ->                              -- property_name : TBasicType TUTF8
    IO (Ptr PropertyAction)

-- | Creates a t'GI.Gio.Interfaces.Action.Action' corresponding to the value of property
-- /@propertyName@/ on /@object@/.
-- 
-- The property must be existent and readable and writable (and not
-- construct-only).
-- 
-- This function takes a reference on /@object@/ and doesn\'t release it
-- until the action is destroyed.
-- 
-- /Since: 2.38/
propertyActionNew ::
    (B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a) =>
    T.Text
    -- ^ /@name@/: the name of the action to create
    -> a
    -- ^ /@object@/: the object that has the property
    --   to wrap
    -> T.Text
    -- ^ /@propertyName@/: the name of the property
    -> m PropertyAction
    -- ^ __Returns:__ a new t'GI.Gio.Objects.PropertyAction.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