{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gio.Interfaces.ActionGroup.ActionGroup' represents a group of actions. Actions can be used to
-- expose functionality in a structured way, either from one part of a
-- program to another, or to the outside world. Action groups are often
-- used together with a t'GI.Gio.Objects.MenuModel.MenuModel' that provides additional
-- representation data for displaying the actions to the user, e.g. in
-- a menu.
-- 
-- The main way to interact with the actions in a GActionGroup is to
-- activate them with 'GI.Gio.Interfaces.ActionGroup.actionGroupActivateAction'. Activating an
-- action may require a t'GVariant' parameter. The required type of the
-- parameter can be inquired with 'GI.Gio.Interfaces.ActionGroup.actionGroupGetActionParameterType'.
-- Actions may be disabled, see 'GI.Gio.Interfaces.ActionGroup.actionGroupGetActionEnabled'.
-- Activating a disabled action has no effect.
-- 
-- Actions may optionally have a state in the form of a t'GVariant'. The
-- current state of an action can be inquired with
-- 'GI.Gio.Interfaces.ActionGroup.actionGroupGetActionState'. Activating a stateful action may
-- change its state, but it is also possible to set the state by calling
-- 'GI.Gio.Interfaces.ActionGroup.actionGroupChangeActionState'.
-- 
-- As typical example, consider a text editing application which has an
-- option to change the current font to \'bold\'. A good way to represent
-- this would be a stateful action, with a boolean state. Activating the
-- action would toggle the state.
-- 
-- Each action in the group has a unique name (which is a string).  All
-- method calls, except 'GI.Gio.Interfaces.ActionGroup.actionGroupListActions' take the name of
-- an action as an argument.
-- 
-- The t'GI.Gio.Interfaces.ActionGroup.ActionGroup' API is meant to be the \'public\' API to the action
-- group.  The calls here are exactly the interaction that \'external
-- forces\' (eg: UI, incoming D-Bus messages, etc.) are supposed to have
-- with actions.  \'Internal\' APIs (ie: ones meant only to be accessed by
-- the action group implementation) are found on subclasses.  This is
-- why you will find - for example - 'GI.Gio.Interfaces.ActionGroup.actionGroupGetActionEnabled'
-- but not an equivalent @/set()/@ call.
-- 
-- Signals are emitted on the action group in response to state changes
-- on individual actions.
-- 
-- Implementations of t'GI.Gio.Interfaces.ActionGroup.ActionGroup' should provide implementations for
-- the virtual functions 'GI.Gio.Interfaces.ActionGroup.actionGroupListActions' and
-- 'GI.Gio.Interfaces.ActionGroup.actionGroupQueryAction'.  The other virtual functions should
-- not be implemented - their \"wrappers\" are actually implemented with
-- calls to 'GI.Gio.Interfaces.ActionGroup.actionGroupQueryAction'.

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

module GI.Gio.Interfaces.ActionGroup
    ( 

-- * Exported types
    ActionGroup(..)                         ,
    noActionGroup                           ,
    IsActionGroup                           ,
    toActionGroup                           ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveActionGroupMethod                ,
#endif


-- ** actionAdded #method:actionAdded#

#if defined(ENABLE_OVERLOADING)
    ActionGroupActionAddedMethodInfo        ,
#endif
    actionGroupActionAdded                  ,


-- ** actionEnabledChanged #method:actionEnabledChanged#

#if defined(ENABLE_OVERLOADING)
    ActionGroupActionEnabledChangedMethodInfo,
#endif
    actionGroupActionEnabledChanged         ,


-- ** actionRemoved #method:actionRemoved#

#if defined(ENABLE_OVERLOADING)
    ActionGroupActionRemovedMethodInfo      ,
#endif
    actionGroupActionRemoved                ,


-- ** actionStateChanged #method:actionStateChanged#

#if defined(ENABLE_OVERLOADING)
    ActionGroupActionStateChangedMethodInfo ,
#endif
    actionGroupActionStateChanged           ,


-- ** activateAction #method:activateAction#

#if defined(ENABLE_OVERLOADING)
    ActionGroupActivateActionMethodInfo     ,
#endif
    actionGroupActivateAction               ,


-- ** changeActionState #method:changeActionState#

#if defined(ENABLE_OVERLOADING)
    ActionGroupChangeActionStateMethodInfo  ,
#endif
    actionGroupChangeActionState            ,


-- ** getActionEnabled #method:getActionEnabled#

#if defined(ENABLE_OVERLOADING)
    ActionGroupGetActionEnabledMethodInfo   ,
#endif
    actionGroupGetActionEnabled             ,


-- ** getActionParameterType #method:getActionParameterType#

#if defined(ENABLE_OVERLOADING)
    ActionGroupGetActionParameterTypeMethodInfo,
#endif
    actionGroupGetActionParameterType       ,


-- ** getActionState #method:getActionState#

#if defined(ENABLE_OVERLOADING)
    ActionGroupGetActionStateMethodInfo     ,
#endif
    actionGroupGetActionState               ,


-- ** getActionStateHint #method:getActionStateHint#

#if defined(ENABLE_OVERLOADING)
    ActionGroupGetActionStateHintMethodInfo ,
#endif
    actionGroupGetActionStateHint           ,


-- ** getActionStateType #method:getActionStateType#

#if defined(ENABLE_OVERLOADING)
    ActionGroupGetActionStateTypeMethodInfo ,
#endif
    actionGroupGetActionStateType           ,


-- ** hasAction #method:hasAction#

#if defined(ENABLE_OVERLOADING)
    ActionGroupHasActionMethodInfo          ,
#endif
    actionGroupHasAction                    ,


-- ** listActions #method:listActions#

#if defined(ENABLE_OVERLOADING)
    ActionGroupListActionsMethodInfo        ,
#endif
    actionGroupListActions                  ,


-- ** queryAction #method:queryAction#

#if defined(ENABLE_OVERLOADING)
    ActionGroupQueryActionMethodInfo        ,
#endif
    actionGroupQueryAction                  ,




 -- * Signals
-- ** actionAdded #signal:actionAdded#

    ActionGroupActionAddedCallback          ,
#if defined(ENABLE_OVERLOADING)
    ActionGroupActionAddedSignalInfo        ,
#endif
    C_ActionGroupActionAddedCallback        ,
    afterActionGroupActionAdded             ,
    genClosure_ActionGroupActionAdded       ,
    mk_ActionGroupActionAddedCallback       ,
    noActionGroupActionAddedCallback        ,
    onActionGroupActionAdded                ,
    wrap_ActionGroupActionAddedCallback     ,


-- ** actionEnabledChanged #signal:actionEnabledChanged#

    ActionGroupActionEnabledChangedCallback ,
#if defined(ENABLE_OVERLOADING)
    ActionGroupActionEnabledChangedSignalInfo,
#endif
    C_ActionGroupActionEnabledChangedCallback,
    afterActionGroupActionEnabledChanged    ,
    genClosure_ActionGroupActionEnabledChanged,
    mk_ActionGroupActionEnabledChangedCallback,
    noActionGroupActionEnabledChangedCallback,
    onActionGroupActionEnabledChanged       ,
    wrap_ActionGroupActionEnabledChangedCallback,


-- ** actionRemoved #signal:actionRemoved#

    ActionGroupActionRemovedCallback        ,
#if defined(ENABLE_OVERLOADING)
    ActionGroupActionRemovedSignalInfo      ,
#endif
    C_ActionGroupActionRemovedCallback      ,
    afterActionGroupActionRemoved           ,
    genClosure_ActionGroupActionRemoved     ,
    mk_ActionGroupActionRemovedCallback     ,
    noActionGroupActionRemovedCallback      ,
    onActionGroupActionRemoved              ,
    wrap_ActionGroupActionRemovedCallback   ,


-- ** actionStateChanged #signal:actionStateChanged#

    ActionGroupActionStateChangedCallback   ,
#if defined(ENABLE_OVERLOADING)
    ActionGroupActionStateChangedSignalInfo ,
#endif
    C_ActionGroupActionStateChangedCallback ,
    afterActionGroupActionStateChanged      ,
    genClosure_ActionGroupActionStateChanged,
    mk_ActionGroupActionStateChangedCallback,
    noActionGroupActionStateChangedCallback ,
    onActionGroupActionStateChanged         ,
    wrap_ActionGroupActionStateChangedCallback,




    ) 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

-- interface ActionGroup 
-- | Memory-managed wrapper type.
newtype ActionGroup = ActionGroup (ManagedPtr ActionGroup)
    deriving (ActionGroup -> ActionGroup -> Bool
(ActionGroup -> ActionGroup -> Bool)
-> (ActionGroup -> ActionGroup -> Bool) -> Eq ActionGroup
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ActionGroup -> ActionGroup -> Bool
$c/= :: ActionGroup -> ActionGroup -> Bool
== :: ActionGroup -> ActionGroup -> Bool
$c== :: ActionGroup -> ActionGroup -> Bool
Eq)
-- | A convenience alias for `Nothing` :: `Maybe` `ActionGroup`.
noActionGroup :: Maybe ActionGroup
noActionGroup :: Maybe ActionGroup
noActionGroup = Maybe ActionGroup
forall a. Maybe a
Nothing

-- signal ActionGroup::action-added
-- | Signals that a new action was just added to the group.
-- This signal is emitted after the action has been added
-- and is now visible.
-- 
-- /Since: 2.28/
type ActionGroupActionAddedCallback =
    T.Text
    -- ^ /@actionName@/: the name of the action in /@actionGroup@/
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `ActionGroupActionAddedCallback`@.
noActionGroupActionAddedCallback :: Maybe ActionGroupActionAddedCallback
noActionGroupActionAddedCallback :: Maybe ActionGroupActionAddedCallback
noActionGroupActionAddedCallback = Maybe ActionGroupActionAddedCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_ActionGroupActionAddedCallback =
    Ptr () ->                               -- object
    CString ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_ActionGroupActionAddedCallback`.
foreign import ccall "wrapper"
    mk_ActionGroupActionAddedCallback :: C_ActionGroupActionAddedCallback -> IO (FunPtr C_ActionGroupActionAddedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_ActionGroupActionAdded :: MonadIO m => ActionGroupActionAddedCallback -> m (GClosure C_ActionGroupActionAddedCallback)
genClosure_ActionGroupActionAdded :: ActionGroupActionAddedCallback
-> m (GClosure C_ActionGroupActionAddedCallback)
genClosure_ActionGroupActionAdded cb :: ActionGroupActionAddedCallback
cb = IO (GClosure C_ActionGroupActionAddedCallback)
-> m (GClosure C_ActionGroupActionAddedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ActionGroupActionAddedCallback)
 -> m (GClosure C_ActionGroupActionAddedCallback))
-> IO (GClosure C_ActionGroupActionAddedCallback)
-> m (GClosure C_ActionGroupActionAddedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ActionGroupActionAddedCallback
cb' = ActionGroupActionAddedCallback -> C_ActionGroupActionAddedCallback
wrap_ActionGroupActionAddedCallback ActionGroupActionAddedCallback
cb
    C_ActionGroupActionAddedCallback
-> IO (FunPtr C_ActionGroupActionAddedCallback)
mk_ActionGroupActionAddedCallback C_ActionGroupActionAddedCallback
cb' IO (FunPtr C_ActionGroupActionAddedCallback)
-> (FunPtr C_ActionGroupActionAddedCallback
    -> IO (GClosure C_ActionGroupActionAddedCallback))
-> IO (GClosure C_ActionGroupActionAddedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ActionGroupActionAddedCallback
-> IO (GClosure C_ActionGroupActionAddedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `ActionGroupActionAddedCallback` into a `C_ActionGroupActionAddedCallback`.
wrap_ActionGroupActionAddedCallback ::
    ActionGroupActionAddedCallback ->
    C_ActionGroupActionAddedCallback
wrap_ActionGroupActionAddedCallback :: ActionGroupActionAddedCallback -> C_ActionGroupActionAddedCallback
wrap_ActionGroupActionAddedCallback _cb :: ActionGroupActionAddedCallback
_cb _ actionName :: CString
actionName _ = do
    Text
actionName' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
actionName
    ActionGroupActionAddedCallback
_cb  Text
actionName'


-- | Connect a signal handler for the [actionAdded](#signal:actionAdded) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' actionGroup #actionAdded callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@action-added::detail@” instead.
-- 
onActionGroupActionAdded :: (IsActionGroup a, MonadIO m) => a -> P.Maybe T.Text -> ActionGroupActionAddedCallback -> m SignalHandlerId
onActionGroupActionAdded :: a
-> Maybe Text
-> ActionGroupActionAddedCallback
-> m SignalHandlerId
onActionGroupActionAdded obj :: a
obj detail :: Maybe Text
detail cb :: ActionGroupActionAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ActionGroupActionAddedCallback
cb' = ActionGroupActionAddedCallback -> C_ActionGroupActionAddedCallback
wrap_ActionGroupActionAddedCallback ActionGroupActionAddedCallback
cb
    FunPtr C_ActionGroupActionAddedCallback
cb'' <- C_ActionGroupActionAddedCallback
-> IO (FunPtr C_ActionGroupActionAddedCallback)
mk_ActionGroupActionAddedCallback C_ActionGroupActionAddedCallback
cb'
    a
-> Text
-> FunPtr C_ActionGroupActionAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "action-added" FunPtr C_ActionGroupActionAddedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
detail

-- | Connect a signal handler for the [actionAdded](#signal:actionAdded) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' actionGroup #actionAdded callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@action-added::detail@” instead.
-- 
afterActionGroupActionAdded :: (IsActionGroup a, MonadIO m) => a -> P.Maybe T.Text -> ActionGroupActionAddedCallback -> m SignalHandlerId
afterActionGroupActionAdded :: a
-> Maybe Text
-> ActionGroupActionAddedCallback
-> m SignalHandlerId
afterActionGroupActionAdded obj :: a
obj detail :: Maybe Text
detail cb :: ActionGroupActionAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ActionGroupActionAddedCallback
cb' = ActionGroupActionAddedCallback -> C_ActionGroupActionAddedCallback
wrap_ActionGroupActionAddedCallback ActionGroupActionAddedCallback
cb
    FunPtr C_ActionGroupActionAddedCallback
cb'' <- C_ActionGroupActionAddedCallback
-> IO (FunPtr C_ActionGroupActionAddedCallback)
mk_ActionGroupActionAddedCallback C_ActionGroupActionAddedCallback
cb'
    a
-> Text
-> FunPtr C_ActionGroupActionAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "action-added" FunPtr C_ActionGroupActionAddedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
detail


#if defined(ENABLE_OVERLOADING)
data ActionGroupActionAddedSignalInfo
instance SignalInfo ActionGroupActionAddedSignalInfo where
    type HaskellCallbackType ActionGroupActionAddedSignalInfo = ActionGroupActionAddedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ActionGroupActionAddedCallback cb
        cb'' <- mk_ActionGroupActionAddedCallback cb'
        connectSignalFunPtr obj "action-added" cb'' connectMode detail

#endif

-- signal ActionGroup::action-enabled-changed
-- | Signals that the enabled status of the named action has changed.
-- 
-- /Since: 2.28/
type ActionGroupActionEnabledChangedCallback =
    T.Text
    -- ^ /@actionName@/: the name of the action in /@actionGroup@/
    -> Bool
    -- ^ /@enabled@/: whether the action is enabled or not
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `ActionGroupActionEnabledChangedCallback`@.
noActionGroupActionEnabledChangedCallback :: Maybe ActionGroupActionEnabledChangedCallback
noActionGroupActionEnabledChangedCallback :: Maybe ActionGroupActionEnabledChangedCallback
noActionGroupActionEnabledChangedCallback = Maybe ActionGroupActionEnabledChangedCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_ActionGroupActionEnabledChangedCallback =
    Ptr () ->                               -- object
    CString ->
    CInt ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_ActionGroupActionEnabledChangedCallback`.
foreign import ccall "wrapper"
    mk_ActionGroupActionEnabledChangedCallback :: C_ActionGroupActionEnabledChangedCallback -> IO (FunPtr C_ActionGroupActionEnabledChangedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_ActionGroupActionEnabledChanged :: MonadIO m => ActionGroupActionEnabledChangedCallback -> m (GClosure C_ActionGroupActionEnabledChangedCallback)
genClosure_ActionGroupActionEnabledChanged :: ActionGroupActionEnabledChangedCallback
-> m (GClosure C_ActionGroupActionEnabledChangedCallback)
genClosure_ActionGroupActionEnabledChanged cb :: ActionGroupActionEnabledChangedCallback
cb = IO (GClosure C_ActionGroupActionEnabledChangedCallback)
-> m (GClosure C_ActionGroupActionEnabledChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ActionGroupActionEnabledChangedCallback)
 -> m (GClosure C_ActionGroupActionEnabledChangedCallback))
-> IO (GClosure C_ActionGroupActionEnabledChangedCallback)
-> m (GClosure C_ActionGroupActionEnabledChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ActionGroupActionEnabledChangedCallback
cb' = ActionGroupActionEnabledChangedCallback
-> C_ActionGroupActionEnabledChangedCallback
wrap_ActionGroupActionEnabledChangedCallback ActionGroupActionEnabledChangedCallback
cb
    C_ActionGroupActionEnabledChangedCallback
-> IO (FunPtr C_ActionGroupActionEnabledChangedCallback)
mk_ActionGroupActionEnabledChangedCallback C_ActionGroupActionEnabledChangedCallback
cb' IO (FunPtr C_ActionGroupActionEnabledChangedCallback)
-> (FunPtr C_ActionGroupActionEnabledChangedCallback
    -> IO (GClosure C_ActionGroupActionEnabledChangedCallback))
-> IO (GClosure C_ActionGroupActionEnabledChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ActionGroupActionEnabledChangedCallback
-> IO (GClosure C_ActionGroupActionEnabledChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `ActionGroupActionEnabledChangedCallback` into a `C_ActionGroupActionEnabledChangedCallback`.
wrap_ActionGroupActionEnabledChangedCallback ::
    ActionGroupActionEnabledChangedCallback ->
    C_ActionGroupActionEnabledChangedCallback
wrap_ActionGroupActionEnabledChangedCallback :: ActionGroupActionEnabledChangedCallback
-> C_ActionGroupActionEnabledChangedCallback
wrap_ActionGroupActionEnabledChangedCallback _cb :: ActionGroupActionEnabledChangedCallback
_cb _ actionName :: CString
actionName enabled :: CInt
enabled _ = do
    Text
actionName' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
actionName
    let enabled' :: Bool
enabled' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
enabled
    ActionGroupActionEnabledChangedCallback
_cb  Text
actionName' Bool
enabled'


-- | Connect a signal handler for the [actionEnabledChanged](#signal:actionEnabledChanged) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' actionGroup #actionEnabledChanged callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@action-enabled-changed::detail@” instead.
-- 
onActionGroupActionEnabledChanged :: (IsActionGroup a, MonadIO m) => a -> P.Maybe T.Text -> ActionGroupActionEnabledChangedCallback -> m SignalHandlerId
onActionGroupActionEnabledChanged :: a
-> Maybe Text
-> ActionGroupActionEnabledChangedCallback
-> m SignalHandlerId
onActionGroupActionEnabledChanged obj :: a
obj detail :: Maybe Text
detail cb :: ActionGroupActionEnabledChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ActionGroupActionEnabledChangedCallback
cb' = ActionGroupActionEnabledChangedCallback
-> C_ActionGroupActionEnabledChangedCallback
wrap_ActionGroupActionEnabledChangedCallback ActionGroupActionEnabledChangedCallback
cb
    FunPtr C_ActionGroupActionEnabledChangedCallback
cb'' <- C_ActionGroupActionEnabledChangedCallback
-> IO (FunPtr C_ActionGroupActionEnabledChangedCallback)
mk_ActionGroupActionEnabledChangedCallback C_ActionGroupActionEnabledChangedCallback
cb'
    a
-> Text
-> FunPtr C_ActionGroupActionEnabledChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "action-enabled-changed" FunPtr C_ActionGroupActionEnabledChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
detail

-- | Connect a signal handler for the [actionEnabledChanged](#signal:actionEnabledChanged) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' actionGroup #actionEnabledChanged callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@action-enabled-changed::detail@” instead.
-- 
afterActionGroupActionEnabledChanged :: (IsActionGroup a, MonadIO m) => a -> P.Maybe T.Text -> ActionGroupActionEnabledChangedCallback -> m SignalHandlerId
afterActionGroupActionEnabledChanged :: a
-> Maybe Text
-> ActionGroupActionEnabledChangedCallback
-> m SignalHandlerId
afterActionGroupActionEnabledChanged obj :: a
obj detail :: Maybe Text
detail cb :: ActionGroupActionEnabledChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ActionGroupActionEnabledChangedCallback
cb' = ActionGroupActionEnabledChangedCallback
-> C_ActionGroupActionEnabledChangedCallback
wrap_ActionGroupActionEnabledChangedCallback ActionGroupActionEnabledChangedCallback
cb
    FunPtr C_ActionGroupActionEnabledChangedCallback
cb'' <- C_ActionGroupActionEnabledChangedCallback
-> IO (FunPtr C_ActionGroupActionEnabledChangedCallback)
mk_ActionGroupActionEnabledChangedCallback C_ActionGroupActionEnabledChangedCallback
cb'
    a
-> Text
-> FunPtr C_ActionGroupActionEnabledChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "action-enabled-changed" FunPtr C_ActionGroupActionEnabledChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
detail


#if defined(ENABLE_OVERLOADING)
data ActionGroupActionEnabledChangedSignalInfo
instance SignalInfo ActionGroupActionEnabledChangedSignalInfo where
    type HaskellCallbackType ActionGroupActionEnabledChangedSignalInfo = ActionGroupActionEnabledChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ActionGroupActionEnabledChangedCallback cb
        cb'' <- mk_ActionGroupActionEnabledChangedCallback cb'
        connectSignalFunPtr obj "action-enabled-changed" cb'' connectMode detail

#endif

-- signal ActionGroup::action-removed
-- | Signals that an action is just about to be removed from the group.
-- This signal is emitted before the action is removed, so the action
-- is still visible and can be queried from the signal handler.
-- 
-- /Since: 2.28/
type ActionGroupActionRemovedCallback =
    T.Text
    -- ^ /@actionName@/: the name of the action in /@actionGroup@/
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `ActionGroupActionRemovedCallback`@.
noActionGroupActionRemovedCallback :: Maybe ActionGroupActionRemovedCallback
noActionGroupActionRemovedCallback :: Maybe ActionGroupActionAddedCallback
noActionGroupActionRemovedCallback = Maybe ActionGroupActionAddedCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_ActionGroupActionRemovedCallback =
    Ptr () ->                               -- object
    CString ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_ActionGroupActionRemovedCallback`.
foreign import ccall "wrapper"
    mk_ActionGroupActionRemovedCallback :: C_ActionGroupActionRemovedCallback -> IO (FunPtr C_ActionGroupActionRemovedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_ActionGroupActionRemoved :: MonadIO m => ActionGroupActionRemovedCallback -> m (GClosure C_ActionGroupActionRemovedCallback)
genClosure_ActionGroupActionRemoved :: ActionGroupActionAddedCallback
-> m (GClosure C_ActionGroupActionAddedCallback)
genClosure_ActionGroupActionRemoved cb :: ActionGroupActionAddedCallback
cb = IO (GClosure C_ActionGroupActionAddedCallback)
-> m (GClosure C_ActionGroupActionAddedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ActionGroupActionAddedCallback)
 -> m (GClosure C_ActionGroupActionAddedCallback))
-> IO (GClosure C_ActionGroupActionAddedCallback)
-> m (GClosure C_ActionGroupActionAddedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ActionGroupActionAddedCallback
cb' = ActionGroupActionAddedCallback -> C_ActionGroupActionAddedCallback
wrap_ActionGroupActionRemovedCallback ActionGroupActionAddedCallback
cb
    C_ActionGroupActionAddedCallback
-> IO (FunPtr C_ActionGroupActionAddedCallback)
mk_ActionGroupActionRemovedCallback C_ActionGroupActionAddedCallback
cb' IO (FunPtr C_ActionGroupActionAddedCallback)
-> (FunPtr C_ActionGroupActionAddedCallback
    -> IO (GClosure C_ActionGroupActionAddedCallback))
-> IO (GClosure C_ActionGroupActionAddedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ActionGroupActionAddedCallback
-> IO (GClosure C_ActionGroupActionAddedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `ActionGroupActionRemovedCallback` into a `C_ActionGroupActionRemovedCallback`.
wrap_ActionGroupActionRemovedCallback ::
    ActionGroupActionRemovedCallback ->
    C_ActionGroupActionRemovedCallback
wrap_ActionGroupActionRemovedCallback :: ActionGroupActionAddedCallback -> C_ActionGroupActionAddedCallback
wrap_ActionGroupActionRemovedCallback _cb :: ActionGroupActionAddedCallback
_cb _ actionName :: CString
actionName _ = do
    Text
actionName' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
actionName
    ActionGroupActionAddedCallback
_cb  Text
actionName'


-- | Connect a signal handler for the [actionRemoved](#signal:actionRemoved) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' actionGroup #actionRemoved callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@action-removed::detail@” instead.
-- 
onActionGroupActionRemoved :: (IsActionGroup a, MonadIO m) => a -> P.Maybe T.Text -> ActionGroupActionRemovedCallback -> m SignalHandlerId
onActionGroupActionRemoved :: a
-> Maybe Text
-> ActionGroupActionAddedCallback
-> m SignalHandlerId
onActionGroupActionRemoved obj :: a
obj detail :: Maybe Text
detail cb :: ActionGroupActionAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ActionGroupActionAddedCallback
cb' = ActionGroupActionAddedCallback -> C_ActionGroupActionAddedCallback
wrap_ActionGroupActionRemovedCallback ActionGroupActionAddedCallback
cb
    FunPtr C_ActionGroupActionAddedCallback
cb'' <- C_ActionGroupActionAddedCallback
-> IO (FunPtr C_ActionGroupActionAddedCallback)
mk_ActionGroupActionRemovedCallback C_ActionGroupActionAddedCallback
cb'
    a
-> Text
-> FunPtr C_ActionGroupActionAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "action-removed" FunPtr C_ActionGroupActionAddedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
detail

-- | Connect a signal handler for the [actionRemoved](#signal:actionRemoved) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' actionGroup #actionRemoved callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@action-removed::detail@” instead.
-- 
afterActionGroupActionRemoved :: (IsActionGroup a, MonadIO m) => a -> P.Maybe T.Text -> ActionGroupActionRemovedCallback -> m SignalHandlerId
afterActionGroupActionRemoved :: a
-> Maybe Text
-> ActionGroupActionAddedCallback
-> m SignalHandlerId
afterActionGroupActionRemoved obj :: a
obj detail :: Maybe Text
detail cb :: ActionGroupActionAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ActionGroupActionAddedCallback
cb' = ActionGroupActionAddedCallback -> C_ActionGroupActionAddedCallback
wrap_ActionGroupActionRemovedCallback ActionGroupActionAddedCallback
cb
    FunPtr C_ActionGroupActionAddedCallback
cb'' <- C_ActionGroupActionAddedCallback
-> IO (FunPtr C_ActionGroupActionAddedCallback)
mk_ActionGroupActionRemovedCallback C_ActionGroupActionAddedCallback
cb'
    a
-> Text
-> FunPtr C_ActionGroupActionAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "action-removed" FunPtr C_ActionGroupActionAddedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
detail


#if defined(ENABLE_OVERLOADING)
data ActionGroupActionRemovedSignalInfo
instance SignalInfo ActionGroupActionRemovedSignalInfo where
    type HaskellCallbackType ActionGroupActionRemovedSignalInfo = ActionGroupActionRemovedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ActionGroupActionRemovedCallback cb
        cb'' <- mk_ActionGroupActionRemovedCallback cb'
        connectSignalFunPtr obj "action-removed" cb'' connectMode detail

#endif

-- signal ActionGroup::action-state-changed
-- | Signals that the state of the named action has changed.
-- 
-- /Since: 2.28/
type ActionGroupActionStateChangedCallback =
    T.Text
    -- ^ /@actionName@/: the name of the action in /@actionGroup@/
    -> GVariant
    -- ^ /@value@/: the new value of the state
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `ActionGroupActionStateChangedCallback`@.
noActionGroupActionStateChangedCallback :: Maybe ActionGroupActionStateChangedCallback
noActionGroupActionStateChangedCallback :: Maybe ActionGroupActionStateChangedCallback
noActionGroupActionStateChangedCallback = Maybe ActionGroupActionStateChangedCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_ActionGroupActionStateChangedCallback =
    Ptr () ->                               -- object
    CString ->
    Ptr GVariant ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_ActionGroupActionStateChangedCallback`.
foreign import ccall "wrapper"
    mk_ActionGroupActionStateChangedCallback :: C_ActionGroupActionStateChangedCallback -> IO (FunPtr C_ActionGroupActionStateChangedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_ActionGroupActionStateChanged :: MonadIO m => ActionGroupActionStateChangedCallback -> m (GClosure C_ActionGroupActionStateChangedCallback)
genClosure_ActionGroupActionStateChanged :: ActionGroupActionStateChangedCallback
-> m (GClosure C_ActionGroupActionStateChangedCallback)
genClosure_ActionGroupActionStateChanged cb :: ActionGroupActionStateChangedCallback
cb = IO (GClosure C_ActionGroupActionStateChangedCallback)
-> m (GClosure C_ActionGroupActionStateChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ActionGroupActionStateChangedCallback)
 -> m (GClosure C_ActionGroupActionStateChangedCallback))
-> IO (GClosure C_ActionGroupActionStateChangedCallback)
-> m (GClosure C_ActionGroupActionStateChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ActionGroupActionStateChangedCallback
cb' = ActionGroupActionStateChangedCallback
-> C_ActionGroupActionStateChangedCallback
wrap_ActionGroupActionStateChangedCallback ActionGroupActionStateChangedCallback
cb
    C_ActionGroupActionStateChangedCallback
-> IO (FunPtr C_ActionGroupActionStateChangedCallback)
mk_ActionGroupActionStateChangedCallback C_ActionGroupActionStateChangedCallback
cb' IO (FunPtr C_ActionGroupActionStateChangedCallback)
-> (FunPtr C_ActionGroupActionStateChangedCallback
    -> IO (GClosure C_ActionGroupActionStateChangedCallback))
-> IO (GClosure C_ActionGroupActionStateChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ActionGroupActionStateChangedCallback
-> IO (GClosure C_ActionGroupActionStateChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `ActionGroupActionStateChangedCallback` into a `C_ActionGroupActionStateChangedCallback`.
wrap_ActionGroupActionStateChangedCallback ::
    ActionGroupActionStateChangedCallback ->
    C_ActionGroupActionStateChangedCallback
wrap_ActionGroupActionStateChangedCallback :: ActionGroupActionStateChangedCallback
-> C_ActionGroupActionStateChangedCallback
wrap_ActionGroupActionStateChangedCallback _cb :: ActionGroupActionStateChangedCallback
_cb _ actionName :: CString
actionName value :: Ptr GVariant
value _ = do
    Text
actionName' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
actionName
    GVariant
value' <- Ptr GVariant -> IO GVariant
B.GVariant.newGVariantFromPtr Ptr GVariant
value
    ActionGroupActionStateChangedCallback
_cb  Text
actionName' GVariant
value'


-- | Connect a signal handler for the [actionStateChanged](#signal:actionStateChanged) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' actionGroup #actionStateChanged callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@action-state-changed::detail@” instead.
-- 
onActionGroupActionStateChanged :: (IsActionGroup a, MonadIO m) => a -> P.Maybe T.Text -> ActionGroupActionStateChangedCallback -> m SignalHandlerId
onActionGroupActionStateChanged :: a
-> Maybe Text
-> ActionGroupActionStateChangedCallback
-> m SignalHandlerId
onActionGroupActionStateChanged obj :: a
obj detail :: Maybe Text
detail cb :: ActionGroupActionStateChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ActionGroupActionStateChangedCallback
cb' = ActionGroupActionStateChangedCallback
-> C_ActionGroupActionStateChangedCallback
wrap_ActionGroupActionStateChangedCallback ActionGroupActionStateChangedCallback
cb
    FunPtr C_ActionGroupActionStateChangedCallback
cb'' <- C_ActionGroupActionStateChangedCallback
-> IO (FunPtr C_ActionGroupActionStateChangedCallback)
mk_ActionGroupActionStateChangedCallback C_ActionGroupActionStateChangedCallback
cb'
    a
-> Text
-> FunPtr C_ActionGroupActionStateChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "action-state-changed" FunPtr C_ActionGroupActionStateChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
detail

-- | Connect a signal handler for the [actionStateChanged](#signal:actionStateChanged) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' actionGroup #actionStateChanged callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@action-state-changed::detail@” instead.
-- 
afterActionGroupActionStateChanged :: (IsActionGroup a, MonadIO m) => a -> P.Maybe T.Text -> ActionGroupActionStateChangedCallback -> m SignalHandlerId
afterActionGroupActionStateChanged :: a
-> Maybe Text
-> ActionGroupActionStateChangedCallback
-> m SignalHandlerId
afterActionGroupActionStateChanged obj :: a
obj detail :: Maybe Text
detail cb :: ActionGroupActionStateChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ActionGroupActionStateChangedCallback
cb' = ActionGroupActionStateChangedCallback
-> C_ActionGroupActionStateChangedCallback
wrap_ActionGroupActionStateChangedCallback ActionGroupActionStateChangedCallback
cb
    FunPtr C_ActionGroupActionStateChangedCallback
cb'' <- C_ActionGroupActionStateChangedCallback
-> IO (FunPtr C_ActionGroupActionStateChangedCallback)
mk_ActionGroupActionStateChangedCallback C_ActionGroupActionStateChangedCallback
cb'
    a
-> Text
-> FunPtr C_ActionGroupActionStateChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "action-state-changed" FunPtr C_ActionGroupActionStateChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
detail


#if defined(ENABLE_OVERLOADING)
data ActionGroupActionStateChangedSignalInfo
instance SignalInfo ActionGroupActionStateChangedSignalInfo where
    type HaskellCallbackType ActionGroupActionStateChangedSignalInfo = ActionGroupActionStateChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ActionGroupActionStateChangedCallback cb
        cb'' <- mk_ActionGroupActionStateChangedCallback cb'
        connectSignalFunPtr obj "action-state-changed" cb'' connectMode detail

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ActionGroup = ActionGroupSignalList
type ActionGroupSignalList = ('[ '("actionAdded", ActionGroupActionAddedSignalInfo), '("actionEnabledChanged", ActionGroupActionEnabledChangedSignalInfo), '("actionRemoved", ActionGroupActionRemovedSignalInfo), '("actionStateChanged", ActionGroupActionStateChangedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

foreign import ccall "g_action_group_get_type"
    c_g_action_group_get_type :: IO GType

instance GObject ActionGroup where
    gobjectType :: IO GType
gobjectType = IO GType
c_g_action_group_get_type
    

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

-- | Type class for types which can be safely cast to `ActionGroup`, for instance with `toActionGroup`.
class (GObject o, O.IsDescendantOf ActionGroup o) => IsActionGroup o
instance (GObject o, O.IsDescendantOf ActionGroup o) => IsActionGroup o

instance O.HasParentTypes ActionGroup
type instance O.ParentTypes ActionGroup = '[GObject.Object.Object]

-- | Cast to `ActionGroup`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toActionGroup :: (MonadIO m, IsActionGroup o) => o -> m ActionGroup
toActionGroup :: o -> m ActionGroup
toActionGroup = IO ActionGroup -> m ActionGroup
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ActionGroup -> m ActionGroup)
-> (o -> IO ActionGroup) -> o -> m ActionGroup
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr ActionGroup -> ActionGroup) -> o -> IO ActionGroup
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr ActionGroup -> ActionGroup
ActionGroup

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ActionGroup
type instance O.AttributeList ActionGroup = ActionGroupAttributeList
type ActionGroupAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveActionGroupMethod (t :: Symbol) (o :: *) :: * where
    ResolveActionGroupMethod "actionAdded" o = ActionGroupActionAddedMethodInfo
    ResolveActionGroupMethod "actionEnabledChanged" o = ActionGroupActionEnabledChangedMethodInfo
    ResolveActionGroupMethod "actionRemoved" o = ActionGroupActionRemovedMethodInfo
    ResolveActionGroupMethod "actionStateChanged" o = ActionGroupActionStateChangedMethodInfo
    ResolveActionGroupMethod "activateAction" o = ActionGroupActivateActionMethodInfo
    ResolveActionGroupMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveActionGroupMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveActionGroupMethod "changeActionState" o = ActionGroupChangeActionStateMethodInfo
    ResolveActionGroupMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveActionGroupMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveActionGroupMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveActionGroupMethod "hasAction" o = ActionGroupHasActionMethodInfo
    ResolveActionGroupMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveActionGroupMethod "listActions" o = ActionGroupListActionsMethodInfo
    ResolveActionGroupMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveActionGroupMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveActionGroupMethod "queryAction" o = ActionGroupQueryActionMethodInfo
    ResolveActionGroupMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveActionGroupMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveActionGroupMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveActionGroupMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveActionGroupMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveActionGroupMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveActionGroupMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveActionGroupMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveActionGroupMethod "getActionEnabled" o = ActionGroupGetActionEnabledMethodInfo
    ResolveActionGroupMethod "getActionParameterType" o = ActionGroupGetActionParameterTypeMethodInfo
    ResolveActionGroupMethod "getActionState" o = ActionGroupGetActionStateMethodInfo
    ResolveActionGroupMethod "getActionStateHint" o = ActionGroupGetActionStateHintMethodInfo
    ResolveActionGroupMethod "getActionStateType" o = ActionGroupGetActionStateTypeMethodInfo
    ResolveActionGroupMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveActionGroupMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveActionGroupMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveActionGroupMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveActionGroupMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveActionGroupMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveActionGroupMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveActionGroupMethod t ActionGroup, O.MethodInfo info ActionGroup p) => OL.IsLabel t (ActionGroup -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

-- method ActionGroup::action_added
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action_group"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ActionGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GActionGroup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "action_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of an action in the group"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_action_group_action_added" g_action_group_action_added :: 
    Ptr ActionGroup ->                      -- action_group : TInterface (Name {namespace = "Gio", name = "ActionGroup"})
    CString ->                              -- action_name : TBasicType TUTF8
    IO ()

-- | Emits the [actionAdded]("GI.Gio.Interfaces.ActionGroup#signal:actionAdded") signal on /@actionGroup@/.
-- 
-- This function should only be called by t'GI.Gio.Interfaces.ActionGroup.ActionGroup' implementations.
-- 
-- /Since: 2.28/
actionGroupActionAdded ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
    a
    -- ^ /@actionGroup@/: a t'GI.Gio.Interfaces.ActionGroup.ActionGroup'
    -> T.Text
    -- ^ /@actionName@/: the name of an action in the group
    -> m ()
actionGroupActionAdded :: a -> Text -> m ()
actionGroupActionAdded actionGroup :: a
actionGroup actionName :: Text
actionName = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr ActionGroup
actionGroup' <- a -> IO (Ptr ActionGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
actionGroup
    CString
actionName' <- Text -> IO CString
textToCString Text
actionName
    Ptr ActionGroup -> CString -> IO ()
g_action_group_action_added Ptr ActionGroup
actionGroup' CString
actionName'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
actionGroup
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
actionName'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ActionGroupActionAddedMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsActionGroup a) => O.MethodInfo ActionGroupActionAddedMethodInfo a signature where
    overloadedMethod = actionGroupActionAdded

#endif

-- method ActionGroup::action_enabled_changed
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action_group"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ActionGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GActionGroup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "action_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of an action in the group"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "enabled"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether or not the action is now enabled"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_action_group_action_enabled_changed" g_action_group_action_enabled_changed :: 
    Ptr ActionGroup ->                      -- action_group : TInterface (Name {namespace = "Gio", name = "ActionGroup"})
    CString ->                              -- action_name : TBasicType TUTF8
    CInt ->                                 -- enabled : TBasicType TBoolean
    IO ()

-- | Emits the [actionEnabledChanged]("GI.Gio.Interfaces.ActionGroup#signal:actionEnabledChanged") signal on /@actionGroup@/.
-- 
-- This function should only be called by t'GI.Gio.Interfaces.ActionGroup.ActionGroup' implementations.
-- 
-- /Since: 2.28/
actionGroupActionEnabledChanged ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
    a
    -- ^ /@actionGroup@/: a t'GI.Gio.Interfaces.ActionGroup.ActionGroup'
    -> T.Text
    -- ^ /@actionName@/: the name of an action in the group
    -> Bool
    -- ^ /@enabled@/: whether or not the action is now enabled
    -> m ()
actionGroupActionEnabledChanged :: a -> Text -> Bool -> m ()
actionGroupActionEnabledChanged actionGroup :: a
actionGroup actionName :: Text
actionName enabled :: Bool
enabled = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr ActionGroup
actionGroup' <- a -> IO (Ptr ActionGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
actionGroup
    CString
actionName' <- Text -> IO CString
textToCString Text
actionName
    let enabled' :: CInt
enabled' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
enabled
    Ptr ActionGroup -> CString -> CInt -> IO ()
g_action_group_action_enabled_changed Ptr ActionGroup
actionGroup' CString
actionName' CInt
enabled'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
actionGroup
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
actionName'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ActionGroupActionEnabledChangedMethodInfo
instance (signature ~ (T.Text -> Bool -> m ()), MonadIO m, IsActionGroup a) => O.MethodInfo ActionGroupActionEnabledChangedMethodInfo a signature where
    overloadedMethod = actionGroupActionEnabledChanged

#endif

-- method ActionGroup::action_removed
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action_group"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ActionGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GActionGroup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "action_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of an action in the group"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_action_group_action_removed" g_action_group_action_removed :: 
    Ptr ActionGroup ->                      -- action_group : TInterface (Name {namespace = "Gio", name = "ActionGroup"})
    CString ->                              -- action_name : TBasicType TUTF8
    IO ()

-- | Emits the [actionRemoved]("GI.Gio.Interfaces.ActionGroup#signal:actionRemoved") signal on /@actionGroup@/.
-- 
-- This function should only be called by t'GI.Gio.Interfaces.ActionGroup.ActionGroup' implementations.
-- 
-- /Since: 2.28/
actionGroupActionRemoved ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
    a
    -- ^ /@actionGroup@/: a t'GI.Gio.Interfaces.ActionGroup.ActionGroup'
    -> T.Text
    -- ^ /@actionName@/: the name of an action in the group
    -> m ()
actionGroupActionRemoved :: a -> Text -> m ()
actionGroupActionRemoved actionGroup :: a
actionGroup actionName :: Text
actionName = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr ActionGroup
actionGroup' <- a -> IO (Ptr ActionGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
actionGroup
    CString
actionName' <- Text -> IO CString
textToCString Text
actionName
    Ptr ActionGroup -> CString -> IO ()
g_action_group_action_removed Ptr ActionGroup
actionGroup' CString
actionName'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
actionGroup
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
actionName'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ActionGroupActionRemovedMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsActionGroup a) => O.MethodInfo ActionGroupActionRemovedMethodInfo a signature where
    overloadedMethod = actionGroupActionRemoved

#endif

-- method ActionGroup::action_state_changed
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action_group"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ActionGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GActionGroup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "action_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of an action in the group"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "state"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new state of the named action"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_action_group_action_state_changed" g_action_group_action_state_changed :: 
    Ptr ActionGroup ->                      -- action_group : TInterface (Name {namespace = "Gio", name = "ActionGroup"})
    CString ->                              -- action_name : TBasicType TUTF8
    Ptr GVariant ->                         -- state : TVariant
    IO ()

-- | Emits the [actionStateChanged]("GI.Gio.Interfaces.ActionGroup#signal:actionStateChanged") signal on /@actionGroup@/.
-- 
-- This function should only be called by t'GI.Gio.Interfaces.ActionGroup.ActionGroup' implementations.
-- 
-- /Since: 2.28/
actionGroupActionStateChanged ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
    a
    -- ^ /@actionGroup@/: a t'GI.Gio.Interfaces.ActionGroup.ActionGroup'
    -> T.Text
    -- ^ /@actionName@/: the name of an action in the group
    -> GVariant
    -- ^ /@state@/: the new state of the named action
    -> m ()
actionGroupActionStateChanged :: a -> Text -> GVariant -> m ()
actionGroupActionStateChanged actionGroup :: a
actionGroup actionName :: Text
actionName state :: GVariant
state = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr ActionGroup
actionGroup' <- a -> IO (Ptr ActionGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
actionGroup
    CString
actionName' <- Text -> IO CString
textToCString Text
actionName
    Ptr GVariant
state' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
state
    Ptr ActionGroup -> CString -> Ptr GVariant -> IO ()
g_action_group_action_state_changed Ptr ActionGroup
actionGroup' CString
actionName' Ptr GVariant
state'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
actionGroup
    GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GVariant
state
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
actionName'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ActionGroupActionStateChangedMethodInfo
instance (signature ~ (T.Text -> GVariant -> m ()), MonadIO m, IsActionGroup a) => O.MethodInfo ActionGroupActionStateChangedMethodInfo a signature where
    overloadedMethod = actionGroupActionStateChanged

#endif

-- method ActionGroup::activate_action
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action_group"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ActionGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GActionGroup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "action_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the action to activate"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parameter"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "parameters to the activation"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_action_group_activate_action" g_action_group_activate_action :: 
    Ptr ActionGroup ->                      -- action_group : TInterface (Name {namespace = "Gio", name = "ActionGroup"})
    CString ->                              -- action_name : TBasicType TUTF8
    Ptr GVariant ->                         -- parameter : TVariant
    IO ()

-- | Activate the named action within /@actionGroup@/.
-- 
-- If the action is expecting a parameter, then the correct type of
-- parameter must be given as /@parameter@/.  If the action is expecting no
-- parameters then /@parameter@/ must be 'P.Nothing'.  See
-- 'GI.Gio.Interfaces.ActionGroup.actionGroupGetActionParameterType'.
-- 
-- /Since: 2.28/
actionGroupActivateAction ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
    a
    -- ^ /@actionGroup@/: a t'GI.Gio.Interfaces.ActionGroup.ActionGroup'
    -> T.Text
    -- ^ /@actionName@/: the name of the action to activate
    -> Maybe (GVariant)
    -- ^ /@parameter@/: parameters to the activation
    -> m ()
actionGroupActivateAction :: a -> Text -> Maybe GVariant -> m ()
actionGroupActivateAction actionGroup :: a
actionGroup actionName :: Text
actionName parameter :: Maybe GVariant
parameter = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr ActionGroup
actionGroup' <- a -> IO (Ptr ActionGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
actionGroup
    CString
actionName' <- Text -> IO CString
textToCString Text
actionName
    Ptr GVariant
maybeParameter <- case Maybe GVariant
parameter of
        Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
nullPtr
        Just jParameter :: GVariant
jParameter -> do
            Ptr GVariant
jParameter' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jParameter
            Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
jParameter'
    Ptr ActionGroup -> CString -> Ptr GVariant -> IO ()
g_action_group_activate_action Ptr ActionGroup
actionGroup' CString
actionName' Ptr GVariant
maybeParameter
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
actionGroup
    Maybe GVariant -> (GVariant -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe GVariant
parameter GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
actionName'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ActionGroupActivateActionMethodInfo
instance (signature ~ (T.Text -> Maybe (GVariant) -> m ()), MonadIO m, IsActionGroup a) => O.MethodInfo ActionGroupActivateActionMethodInfo a signature where
    overloadedMethod = actionGroupActivateAction

#endif

-- method ActionGroup::change_action_state
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action_group"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ActionGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GActionGroup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "action_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the name of the action to request the change on"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new state" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_action_group_change_action_state" g_action_group_change_action_state :: 
    Ptr ActionGroup ->                      -- action_group : TInterface (Name {namespace = "Gio", name = "ActionGroup"})
    CString ->                              -- action_name : TBasicType TUTF8
    Ptr GVariant ->                         -- value : TVariant
    IO ()

-- | Request for the state of the named action within /@actionGroup@/ to be
-- changed to /@value@/.
-- 
-- The action must be stateful and /@value@/ must be of the correct type.
-- See 'GI.Gio.Interfaces.ActionGroup.actionGroupGetActionStateType'.
-- 
-- This call merely requests a change.  The action may refuse to change
-- its state or may change its state to something other than /@value@/.
-- See 'GI.Gio.Interfaces.ActionGroup.actionGroupGetActionStateHint'.
-- 
-- If the /@value@/ GVariant is floating, it is consumed.
-- 
-- /Since: 2.28/
actionGroupChangeActionState ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
    a
    -- ^ /@actionGroup@/: a t'GI.Gio.Interfaces.ActionGroup.ActionGroup'
    -> T.Text
    -- ^ /@actionName@/: the name of the action to request the change on
    -> GVariant
    -- ^ /@value@/: the new state
    -> m ()
actionGroupChangeActionState :: a -> Text -> GVariant -> m ()
actionGroupChangeActionState actionGroup :: a
actionGroup actionName :: Text
actionName value :: GVariant
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr ActionGroup
actionGroup' <- a -> IO (Ptr ActionGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
actionGroup
    CString
actionName' <- Text -> IO CString
textToCString Text
actionName
    Ptr GVariant
value' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
value
    Ptr ActionGroup -> CString -> Ptr GVariant -> IO ()
g_action_group_change_action_state Ptr ActionGroup
actionGroup' CString
actionName' Ptr GVariant
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
actionGroup
    GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GVariant
value
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
actionName'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ActionGroupChangeActionStateMethodInfo
instance (signature ~ (T.Text -> GVariant -> m ()), MonadIO m, IsActionGroup a) => O.MethodInfo ActionGroupChangeActionStateMethodInfo a signature where
    overloadedMethod = actionGroupChangeActionState

#endif

-- method ActionGroup::get_action_enabled
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action_group"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ActionGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GActionGroup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "action_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the action to query"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_action_group_get_action_enabled" g_action_group_get_action_enabled :: 
    Ptr ActionGroup ->                      -- action_group : TInterface (Name {namespace = "Gio", name = "ActionGroup"})
    CString ->                              -- action_name : TBasicType TUTF8
    IO CInt

-- | Checks if the named action within /@actionGroup@/ is currently enabled.
-- 
-- An action must be enabled in order to be activated or in order to
-- have its state changed from outside callers.
-- 
-- /Since: 2.28/
actionGroupGetActionEnabled ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
    a
    -- ^ /@actionGroup@/: a t'GI.Gio.Interfaces.ActionGroup.ActionGroup'
    -> T.Text
    -- ^ /@actionName@/: the name of the action to query
    -> m Bool
    -- ^ __Returns:__ whether or not the action is currently enabled
actionGroupGetActionEnabled :: a -> Text -> m Bool
actionGroupGetActionEnabled actionGroup :: a
actionGroup actionName :: Text
actionName = 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
$ do
    Ptr ActionGroup
actionGroup' <- a -> IO (Ptr ActionGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
actionGroup
    CString
actionName' <- Text -> IO CString
textToCString Text
actionName
    CInt
result <- Ptr ActionGroup -> CString -> IO CInt
g_action_group_get_action_enabled Ptr ActionGroup
actionGroup' CString
actionName'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
actionGroup
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
actionName'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ActionGroupGetActionEnabledMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsActionGroup a) => O.MethodInfo ActionGroupGetActionEnabledMethodInfo a signature where
    overloadedMethod = actionGroupGetActionEnabled

#endif

-- method ActionGroup::get_action_parameter_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action_group"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ActionGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GActionGroup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "action_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the action to query"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GLib" , name = "VariantType" })
-- throws : False
-- Skip return : False

foreign import ccall "g_action_group_get_action_parameter_type" g_action_group_get_action_parameter_type :: 
    Ptr ActionGroup ->                      -- action_group : TInterface (Name {namespace = "Gio", name = "ActionGroup"})
    CString ->                              -- action_name : TBasicType TUTF8
    IO (Ptr GLib.VariantType.VariantType)

-- | Queries the type of the parameter that must be given when activating
-- the named action within /@actionGroup@/.
-- 
-- When activating the action using 'GI.Gio.Interfaces.ActionGroup.actionGroupActivateAction',
-- the t'GVariant' given to that function must be of the type returned
-- by this function.
-- 
-- In the case that this function returns 'P.Nothing', you must not give any
-- t'GVariant', but 'P.Nothing' instead.
-- 
-- The parameter type of a particular action will never change but it is
-- possible for an action to be removed and for a new action to be added
-- with the same name but a different parameter type.
-- 
-- /Since: 2.28/
actionGroupGetActionParameterType ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
    a
    -- ^ /@actionGroup@/: a t'GI.Gio.Interfaces.ActionGroup.ActionGroup'
    -> T.Text
    -- ^ /@actionName@/: the name of the action to query
    -> m (Maybe GLib.VariantType.VariantType)
    -- ^ __Returns:__ the parameter type
actionGroupGetActionParameterType :: a -> Text -> m (Maybe VariantType)
actionGroupGetActionParameterType actionGroup :: a
actionGroup actionName :: Text
actionName = 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
$ do
    Ptr ActionGroup
actionGroup' <- a -> IO (Ptr ActionGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
actionGroup
    CString
actionName' <- Text -> IO CString
textToCString Text
actionName
    Ptr VariantType
result <- Ptr ActionGroup -> CString -> IO (Ptr VariantType)
g_action_group_get_action_parameter_type Ptr ActionGroup
actionGroup' CString
actionName'
    Maybe VariantType
maybeResult <- Ptr VariantType
-> (Ptr VariantType -> IO VariantType) -> IO (Maybe VariantType)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr VariantType
result ((Ptr VariantType -> IO VariantType) -> IO (Maybe VariantType))
-> (Ptr VariantType -> IO VariantType) -> IO (Maybe VariantType)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr VariantType
result' -> do
        VariantType
result'' <- ((ManagedPtr VariantType -> VariantType)
-> Ptr VariantType -> IO VariantType
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr VariantType -> VariantType
GLib.VariantType.VariantType) Ptr VariantType
result'
        VariantType -> IO VariantType
forall (m :: * -> *) a. Monad m => a -> m a
return VariantType
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
actionGroup
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
actionName'
    Maybe VariantType -> IO (Maybe VariantType)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe VariantType
maybeResult

#if defined(ENABLE_OVERLOADING)
data ActionGroupGetActionParameterTypeMethodInfo
instance (signature ~ (T.Text -> m (Maybe GLib.VariantType.VariantType)), MonadIO m, IsActionGroup a) => O.MethodInfo ActionGroupGetActionParameterTypeMethodInfo a signature where
    overloadedMethod = actionGroupGetActionParameterType

#endif

-- method ActionGroup::get_action_state
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action_group"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ActionGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GActionGroup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "action_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the action to query"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TVariant
-- throws : False
-- Skip return : False

foreign import ccall "g_action_group_get_action_state" g_action_group_get_action_state :: 
    Ptr ActionGroup ->                      -- action_group : TInterface (Name {namespace = "Gio", name = "ActionGroup"})
    CString ->                              -- action_name : TBasicType TUTF8
    IO (Ptr GVariant)

-- | Queries the current state of the named action within /@actionGroup@/.
-- 
-- If the action is not stateful then 'P.Nothing' will be returned.  If the
-- action is stateful then the type of the return value is the type
-- given by 'GI.Gio.Interfaces.ActionGroup.actionGroupGetActionStateType'.
-- 
-- The return value (if non-'P.Nothing') should be freed with
-- 'GI.GLib.Structs.Variant.variantUnref' when it is no longer required.
-- 
-- /Since: 2.28/
actionGroupGetActionState ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
    a
    -- ^ /@actionGroup@/: a t'GI.Gio.Interfaces.ActionGroup.ActionGroup'
    -> T.Text
    -- ^ /@actionName@/: the name of the action to query
    -> m (Maybe GVariant)
    -- ^ __Returns:__ the current state of the action
actionGroupGetActionState :: a -> Text -> m (Maybe GVariant)
actionGroupGetActionState actionGroup :: a
actionGroup actionName :: Text
actionName = 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
$ do
    Ptr ActionGroup
actionGroup' <- a -> IO (Ptr ActionGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
actionGroup
    CString
actionName' <- Text -> IO CString
textToCString Text
actionName
    Ptr GVariant
result <- Ptr ActionGroup -> CString -> IO (Ptr GVariant)
g_action_group_get_action_state Ptr ActionGroup
actionGroup' CString
actionName'
    Maybe GVariant
maybeResult <- Ptr GVariant
-> (Ptr GVariant -> IO GVariant) -> IO (Maybe GVariant)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr GVariant
result ((Ptr GVariant -> IO GVariant) -> IO (Maybe GVariant))
-> (Ptr GVariant -> IO GVariant) -> IO (Maybe GVariant)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr GVariant
result' -> do
        GVariant
result'' <- Ptr GVariant -> IO GVariant
B.GVariant.wrapGVariantPtr Ptr GVariant
result'
        GVariant -> IO GVariant
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
actionGroup
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
actionName'
    Maybe GVariant -> IO (Maybe GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GVariant
maybeResult

#if defined(ENABLE_OVERLOADING)
data ActionGroupGetActionStateMethodInfo
instance (signature ~ (T.Text -> m (Maybe GVariant)), MonadIO m, IsActionGroup a) => O.MethodInfo ActionGroupGetActionStateMethodInfo a signature where
    overloadedMethod = actionGroupGetActionState

#endif

-- method ActionGroup::get_action_state_hint
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action_group"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ActionGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GActionGroup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "action_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the action to query"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TVariant
-- throws : False
-- Skip return : False

foreign import ccall "g_action_group_get_action_state_hint" g_action_group_get_action_state_hint :: 
    Ptr ActionGroup ->                      -- action_group : TInterface (Name {namespace = "Gio", name = "ActionGroup"})
    CString ->                              -- action_name : TBasicType TUTF8
    IO (Ptr GVariant)

-- | Requests a hint about the valid range of values for the state of the
-- named action within /@actionGroup@/.
-- 
-- If 'P.Nothing' is returned it either means that the action is not stateful
-- or that there is no hint about the valid range of values for the
-- state of the action.
-- 
-- If a t'GVariant' array is returned then each item in the array is a
-- possible value for the state.  If a t'GVariant' pair (ie: two-tuple) is
-- returned then the tuple specifies the inclusive lower and upper bound
-- of valid values for the state.
-- 
-- In any case, the information is merely a hint.  It may be possible to
-- have a state value outside of the hinted range and setting a value
-- within the range may fail.
-- 
-- The return value (if non-'P.Nothing') should be freed with
-- 'GI.GLib.Structs.Variant.variantUnref' when it is no longer required.
-- 
-- /Since: 2.28/
actionGroupGetActionStateHint ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
    a
    -- ^ /@actionGroup@/: a t'GI.Gio.Interfaces.ActionGroup.ActionGroup'
    -> T.Text
    -- ^ /@actionName@/: the name of the action to query
    -> m (Maybe GVariant)
    -- ^ __Returns:__ the state range hint
actionGroupGetActionStateHint :: a -> Text -> m (Maybe GVariant)
actionGroupGetActionStateHint actionGroup :: a
actionGroup actionName :: Text
actionName = 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
$ do
    Ptr ActionGroup
actionGroup' <- a -> IO (Ptr ActionGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
actionGroup
    CString
actionName' <- Text -> IO CString
textToCString Text
actionName
    Ptr GVariant
result <- Ptr ActionGroup -> CString -> IO (Ptr GVariant)
g_action_group_get_action_state_hint Ptr ActionGroup
actionGroup' CString
actionName'
    Maybe GVariant
maybeResult <- Ptr GVariant
-> (Ptr GVariant -> IO GVariant) -> IO (Maybe GVariant)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr GVariant
result ((Ptr GVariant -> IO GVariant) -> IO (Maybe GVariant))
-> (Ptr GVariant -> IO GVariant) -> IO (Maybe GVariant)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr GVariant
result' -> do
        GVariant
result'' <- Ptr GVariant -> IO GVariant
B.GVariant.wrapGVariantPtr Ptr GVariant
result'
        GVariant -> IO GVariant
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
actionGroup
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
actionName'
    Maybe GVariant -> IO (Maybe GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GVariant
maybeResult

#if defined(ENABLE_OVERLOADING)
data ActionGroupGetActionStateHintMethodInfo
instance (signature ~ (T.Text -> m (Maybe GVariant)), MonadIO m, IsActionGroup a) => O.MethodInfo ActionGroupGetActionStateHintMethodInfo a signature where
    overloadedMethod = actionGroupGetActionStateHint

#endif

-- method ActionGroup::get_action_state_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action_group"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ActionGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GActionGroup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "action_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the action to query"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GLib" , name = "VariantType" })
-- throws : False
-- Skip return : False

foreign import ccall "g_action_group_get_action_state_type" g_action_group_get_action_state_type :: 
    Ptr ActionGroup ->                      -- action_group : TInterface (Name {namespace = "Gio", name = "ActionGroup"})
    CString ->                              -- action_name : TBasicType TUTF8
    IO (Ptr GLib.VariantType.VariantType)

-- | Queries the type of the state of the named action within
-- /@actionGroup@/.
-- 
-- If the action is stateful then this function returns the
-- t'GI.GLib.Structs.VariantType.VariantType' of the state.  All calls to
-- 'GI.Gio.Interfaces.ActionGroup.actionGroupChangeActionState' must give a t'GVariant' of this
-- type and 'GI.Gio.Interfaces.ActionGroup.actionGroupGetActionState' will return a t'GVariant'
-- of the same type.
-- 
-- If the action is not stateful then this function will return 'P.Nothing'.
-- In that case, 'GI.Gio.Interfaces.ActionGroup.actionGroupGetActionState' will return 'P.Nothing'
-- and you must not call 'GI.Gio.Interfaces.ActionGroup.actionGroupChangeActionState'.
-- 
-- The state type of a particular action will never change but it is
-- possible for an action to be removed and for a new action to be added
-- with the same name but a different state type.
-- 
-- /Since: 2.28/
actionGroupGetActionStateType ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
    a
    -- ^ /@actionGroup@/: a t'GI.Gio.Interfaces.ActionGroup.ActionGroup'
    -> T.Text
    -- ^ /@actionName@/: the name of the action to query
    -> m (Maybe GLib.VariantType.VariantType)
    -- ^ __Returns:__ the state type, if the action is stateful
actionGroupGetActionStateType :: a -> Text -> m (Maybe VariantType)
actionGroupGetActionStateType actionGroup :: a
actionGroup actionName :: Text
actionName = 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
$ do
    Ptr ActionGroup
actionGroup' <- a -> IO (Ptr ActionGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
actionGroup
    CString
actionName' <- Text -> IO CString
textToCString Text
actionName
    Ptr VariantType
result <- Ptr ActionGroup -> CString -> IO (Ptr VariantType)
g_action_group_get_action_state_type Ptr ActionGroup
actionGroup' CString
actionName'
    Maybe VariantType
maybeResult <- Ptr VariantType
-> (Ptr VariantType -> IO VariantType) -> IO (Maybe VariantType)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr VariantType
result ((Ptr VariantType -> IO VariantType) -> IO (Maybe VariantType))
-> (Ptr VariantType -> IO VariantType) -> IO (Maybe VariantType)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr VariantType
result' -> do
        VariantType
result'' <- ((ManagedPtr VariantType -> VariantType)
-> Ptr VariantType -> IO VariantType
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr VariantType -> VariantType
GLib.VariantType.VariantType) Ptr VariantType
result'
        VariantType -> IO VariantType
forall (m :: * -> *) a. Monad m => a -> m a
return VariantType
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
actionGroup
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
actionName'
    Maybe VariantType -> IO (Maybe VariantType)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe VariantType
maybeResult

#if defined(ENABLE_OVERLOADING)
data ActionGroupGetActionStateTypeMethodInfo
instance (signature ~ (T.Text -> m (Maybe GLib.VariantType.VariantType)), MonadIO m, IsActionGroup a) => O.MethodInfo ActionGroupGetActionStateTypeMethodInfo a signature where
    overloadedMethod = actionGroupGetActionStateType

#endif

-- method ActionGroup::has_action
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action_group"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ActionGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GActionGroup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "action_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the action to check for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_action_group_has_action" g_action_group_has_action :: 
    Ptr ActionGroup ->                      -- action_group : TInterface (Name {namespace = "Gio", name = "ActionGroup"})
    CString ->                              -- action_name : TBasicType TUTF8
    IO CInt

-- | Checks if the named action exists within /@actionGroup@/.
-- 
-- /Since: 2.28/
actionGroupHasAction ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
    a
    -- ^ /@actionGroup@/: a t'GI.Gio.Interfaces.ActionGroup.ActionGroup'
    -> T.Text
    -- ^ /@actionName@/: the name of the action to check for
    -> m Bool
    -- ^ __Returns:__ whether the named action exists
actionGroupHasAction :: a -> Text -> m Bool
actionGroupHasAction actionGroup :: a
actionGroup actionName :: Text
actionName = 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
$ do
    Ptr ActionGroup
actionGroup' <- a -> IO (Ptr ActionGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
actionGroup
    CString
actionName' <- Text -> IO CString
textToCString Text
actionName
    CInt
result <- Ptr ActionGroup -> CString -> IO CInt
g_action_group_has_action Ptr ActionGroup
actionGroup' CString
actionName'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
actionGroup
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
actionName'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ActionGroupHasActionMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsActionGroup a) => O.MethodInfo ActionGroupHasActionMethodInfo a signature where
    overloadedMethod = actionGroupHasAction

#endif

-- method ActionGroup::list_actions
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action_group"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ActionGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GActionGroup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TCArray True (-1) (-1) (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "g_action_group_list_actions" g_action_group_list_actions :: 
    Ptr ActionGroup ->                      -- action_group : TInterface (Name {namespace = "Gio", name = "ActionGroup"})
    IO (Ptr CString)

-- | Lists the actions contained within /@actionGroup@/.
-- 
-- The caller is responsible for freeing the list with 'GI.GLib.Functions.strfreev' when
-- it is no longer required.
-- 
-- /Since: 2.28/
actionGroupListActions ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
    a
    -- ^ /@actionGroup@/: a t'GI.Gio.Interfaces.ActionGroup.ActionGroup'
    -> m [T.Text]
    -- ^ __Returns:__ a 'P.Nothing'-terminated array of the names of the
    -- actions in the group
actionGroupListActions :: a -> m [Text]
actionGroupListActions actionGroup :: a
actionGroup = IO [Text] -> m [Text]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Text] -> m [Text]) -> IO [Text] -> m [Text]
forall a b. (a -> b) -> a -> b
$ do
    Ptr ActionGroup
actionGroup' <- a -> IO (Ptr ActionGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
actionGroup
    Ptr CString
result <- Ptr ActionGroup -> IO (Ptr CString)
g_action_group_list_actions Ptr ActionGroup
actionGroup'
    Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "actionGroupListActions" Ptr CString
result
    [Text]
result' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result
    (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
actionGroup
    [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'

#if defined(ENABLE_OVERLOADING)
data ActionGroupListActionsMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m, IsActionGroup a) => O.MethodInfo ActionGroupListActionsMethodInfo a signature where
    overloadedMethod = actionGroupListActions

#endif

-- method ActionGroup::query_action
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action_group"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ActionGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GActionGroup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "action_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of an action in the group"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "enabled"
--           , argType = TBasicType TBoolean
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "if the action is presently enabled"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "parameter_type"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "VariantType" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the parameter type, or %NULL if none needed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "state_type"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "VariantType" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the state type, or %NULL if stateless"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "state_hint"
--           , argType = TVariant
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the state hint, or %NULL if none"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "state"
--           , argType = TVariant
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the current state, or %NULL if stateless"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_action_group_query_action" g_action_group_query_action :: 
    Ptr ActionGroup ->                      -- action_group : TInterface (Name {namespace = "Gio", name = "ActionGroup"})
    CString ->                              -- action_name : TBasicType TUTF8
    Ptr CInt ->                             -- enabled : TBasicType TBoolean
    Ptr (Ptr GLib.VariantType.VariantType) -> -- parameter_type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    Ptr (Ptr GLib.VariantType.VariantType) -> -- state_type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    Ptr (Ptr GVariant) ->                   -- state_hint : TVariant
    Ptr (Ptr GVariant) ->                   -- state : TVariant
    IO CInt

-- | Queries all aspects of the named action within an /@actionGroup@/.
-- 
-- This function acquires the information available from
-- 'GI.Gio.Interfaces.ActionGroup.actionGroupHasAction', 'GI.Gio.Interfaces.ActionGroup.actionGroupGetActionEnabled',
-- 'GI.Gio.Interfaces.ActionGroup.actionGroupGetActionParameterType',
-- 'GI.Gio.Interfaces.ActionGroup.actionGroupGetActionStateType',
-- 'GI.Gio.Interfaces.ActionGroup.actionGroupGetActionStateHint' and
-- 'GI.Gio.Interfaces.ActionGroup.actionGroupGetActionState' with a single function call.
-- 
-- This provides two main benefits.
-- 
-- The first is the improvement in efficiency that comes with not having
-- to perform repeated lookups of the action in order to discover
-- different things about it.  The second is that implementing
-- t'GI.Gio.Interfaces.ActionGroup.ActionGroup' can now be done by only overriding this one virtual
-- function.
-- 
-- The interface provides a default implementation of this function that
-- calls the individual functions, as required, to fetch the
-- information.  The interface also provides default implementations of
-- those functions that call this function.  All implementations,
-- therefore, must override either this function or all of the others.
-- 
-- If the action exists, 'P.True' is returned and any of the requested
-- fields (as indicated by having a non-'P.Nothing' reference passed in) are
-- filled.  If the action doesn\'t exist, 'P.False' is returned and the
-- fields may or may not have been modified.
-- 
-- /Since: 2.32/
actionGroupQueryAction ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
    a
    -- ^ /@actionGroup@/: a t'GI.Gio.Interfaces.ActionGroup.ActionGroup'
    -> T.Text
    -- ^ /@actionName@/: the name of an action in the group
    -> m ((Bool, Bool, GLib.VariantType.VariantType, GLib.VariantType.VariantType, GVariant, GVariant))
    -- ^ __Returns:__ 'P.True' if the action exists, else 'P.False'
actionGroupQueryAction :: a
-> Text
-> m (Bool, Bool, VariantType, VariantType, GVariant, GVariant)
actionGroupQueryAction actionGroup :: a
actionGroup actionName :: Text
actionName = IO (Bool, Bool, VariantType, VariantType, GVariant, GVariant)
-> m (Bool, Bool, VariantType, VariantType, GVariant, GVariant)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Bool, VariantType, VariantType, GVariant, GVariant)
 -> m (Bool, Bool, VariantType, VariantType, GVariant, GVariant))
-> IO (Bool, Bool, VariantType, VariantType, GVariant, GVariant)
-> m (Bool, Bool, VariantType, VariantType, GVariant, GVariant)
forall a b. (a -> b) -> a -> b
$ do
    Ptr ActionGroup
actionGroup' <- a -> IO (Ptr ActionGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
actionGroup
    CString
actionName' <- Text -> IO CString
textToCString Text
actionName
    Ptr CInt
enabled <- IO (Ptr CInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CInt)
    Ptr (Ptr VariantType)
parameterType <- IO (Ptr (Ptr VariantType))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr GLib.VariantType.VariantType))
    Ptr (Ptr VariantType)
stateType <- IO (Ptr (Ptr VariantType))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr GLib.VariantType.VariantType))
    Ptr (Ptr GVariant)
stateHint <- IO (Ptr (Ptr GVariant))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr GVariant))
    Ptr (Ptr GVariant)
state <- IO (Ptr (Ptr GVariant))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr GVariant))
    CInt
result <- Ptr ActionGroup
-> CString
-> Ptr CInt
-> Ptr (Ptr VariantType)
-> Ptr (Ptr VariantType)
-> Ptr (Ptr GVariant)
-> Ptr (Ptr GVariant)
-> IO CInt
g_action_group_query_action Ptr ActionGroup
actionGroup' CString
actionName' Ptr CInt
enabled Ptr (Ptr VariantType)
parameterType Ptr (Ptr VariantType)
stateType Ptr (Ptr GVariant)
stateHint Ptr (Ptr GVariant)
state
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    CInt
enabled' <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
enabled
    let enabled'' :: Bool
enabled'' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
enabled'
    Ptr VariantType
parameterType' <- Ptr (Ptr VariantType) -> IO (Ptr VariantType)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr VariantType)
parameterType
    VariantType
parameterType'' <- ((ManagedPtr VariantType -> VariantType)
-> Ptr VariantType -> IO VariantType
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr VariantType -> VariantType
GLib.VariantType.VariantType) Ptr VariantType
parameterType'
    Ptr VariantType
stateType' <- Ptr (Ptr VariantType) -> IO (Ptr VariantType)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr VariantType)
stateType
    VariantType
stateType'' <- ((ManagedPtr VariantType -> VariantType)
-> Ptr VariantType -> IO VariantType
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr VariantType -> VariantType
GLib.VariantType.VariantType) Ptr VariantType
stateType'
    Ptr GVariant
stateHint' <- Ptr (Ptr GVariant) -> IO (Ptr GVariant)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr GVariant)
stateHint
    GVariant
stateHint'' <- Ptr GVariant -> IO GVariant
B.GVariant.wrapGVariantPtr Ptr GVariant
stateHint'
    Ptr GVariant
state' <- Ptr (Ptr GVariant) -> IO (Ptr GVariant)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr GVariant)
state
    GVariant
state'' <- Ptr GVariant -> IO GVariant
B.GVariant.wrapGVariantPtr Ptr GVariant
state'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
actionGroup
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
actionName'
    Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
enabled
    Ptr (Ptr VariantType) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr VariantType)
parameterType
    Ptr (Ptr VariantType) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr VariantType)
stateType
    Ptr (Ptr GVariant) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr GVariant)
stateHint
    Ptr (Ptr GVariant) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr GVariant)
state
    (Bool, Bool, VariantType, VariantType, GVariant, GVariant)
-> IO (Bool, Bool, VariantType, VariantType, GVariant, GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Bool
enabled'', VariantType
parameterType'', VariantType
stateType'', GVariant
stateHint'', GVariant
state'')

#if defined(ENABLE_OVERLOADING)
data ActionGroupQueryActionMethodInfo
instance (signature ~ (T.Text -> m ((Bool, Bool, GLib.VariantType.VariantType, GLib.VariantType.VariantType, GVariant, GVariant))), MonadIO m, IsActionGroup a) => O.MethodInfo ActionGroupQueryActionMethodInfo a signature where
    overloadedMethod = actionGroupQueryAction

#endif