{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Interfaces.ActionGroup
(
ActionGroup(..) ,
noActionGroup ,
IsActionGroup ,
toActionGroup ,
#if defined(ENABLE_OVERLOADING)
ResolveActionGroupMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ActionGroupActionAddedMethodInfo ,
#endif
actionGroupActionAdded ,
#if defined(ENABLE_OVERLOADING)
ActionGroupActionEnabledChangedMethodInfo,
#endif
actionGroupActionEnabledChanged ,
#if defined(ENABLE_OVERLOADING)
ActionGroupActionRemovedMethodInfo ,
#endif
actionGroupActionRemoved ,
#if defined(ENABLE_OVERLOADING)
ActionGroupActionStateChangedMethodInfo ,
#endif
actionGroupActionStateChanged ,
#if defined(ENABLE_OVERLOADING)
ActionGroupActivateActionMethodInfo ,
#endif
actionGroupActivateAction ,
#if defined(ENABLE_OVERLOADING)
ActionGroupChangeActionStateMethodInfo ,
#endif
actionGroupChangeActionState ,
#if defined(ENABLE_OVERLOADING)
ActionGroupGetActionEnabledMethodInfo ,
#endif
actionGroupGetActionEnabled ,
#if defined(ENABLE_OVERLOADING)
ActionGroupGetActionParameterTypeMethodInfo,
#endif
actionGroupGetActionParameterType ,
#if defined(ENABLE_OVERLOADING)
ActionGroupGetActionStateMethodInfo ,
#endif
actionGroupGetActionState ,
#if defined(ENABLE_OVERLOADING)
ActionGroupGetActionStateHintMethodInfo ,
#endif
actionGroupGetActionStateHint ,
#if defined(ENABLE_OVERLOADING)
ActionGroupGetActionStateTypeMethodInfo ,
#endif
actionGroupGetActionStateType ,
#if defined(ENABLE_OVERLOADING)
ActionGroupHasActionMethodInfo ,
#endif
actionGroupHasAction ,
#if defined(ENABLE_OVERLOADING)
ActionGroupListActionsMethodInfo ,
#endif
actionGroupListActions ,
#if defined(ENABLE_OVERLOADING)
ActionGroupQueryActionMethodInfo ,
#endif
actionGroupQueryAction ,
ActionGroupActionAddedCallback ,
#if defined(ENABLE_OVERLOADING)
ActionGroupActionAddedSignalInfo ,
#endif
C_ActionGroupActionAddedCallback ,
afterActionGroupActionAdded ,
genClosure_ActionGroupActionAdded ,
mk_ActionGroupActionAddedCallback ,
noActionGroupActionAddedCallback ,
onActionGroupActionAdded ,
wrap_ActionGroupActionAddedCallback ,
ActionGroupActionEnabledChangedCallback ,
#if defined(ENABLE_OVERLOADING)
ActionGroupActionEnabledChangedSignalInfo,
#endif
C_ActionGroupActionEnabledChangedCallback,
afterActionGroupActionEnabledChanged ,
genClosure_ActionGroupActionEnabledChanged,
mk_ActionGroupActionEnabledChangedCallback,
noActionGroupActionEnabledChangedCallback,
onActionGroupActionEnabledChanged ,
wrap_ActionGroupActionEnabledChangedCallback,
ActionGroupActionRemovedCallback ,
#if defined(ENABLE_OVERLOADING)
ActionGroupActionRemovedSignalInfo ,
#endif
C_ActionGroupActionRemovedCallback ,
afterActionGroupActionRemoved ,
genClosure_ActionGroupActionRemoved ,
mk_ActionGroupActionRemovedCallback ,
noActionGroupActionRemovedCallback ,
onActionGroupActionRemoved ,
wrap_ActionGroupActionRemovedCallback ,
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 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
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)
noActionGroup :: Maybe ActionGroup
noActionGroup :: Maybe ActionGroup
noActionGroup = Maybe ActionGroup
forall a. Maybe a
Nothing
type ActionGroupActionAddedCallback =
T.Text
-> IO ()
noActionGroupActionAddedCallback :: Maybe ActionGroupActionAddedCallback
noActionGroupActionAddedCallback :: Maybe ActionGroupActionAddedCallback
noActionGroupActionAddedCallback = Maybe ActionGroupActionAddedCallback
forall a. Maybe a
Nothing
type C_ActionGroupActionAddedCallback =
Ptr () ->
CString ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_ActionGroupActionAddedCallback :: C_ActionGroupActionAddedCallback -> IO (FunPtr C_ActionGroupActionAddedCallback)
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_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'
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
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
type ActionGroupActionEnabledChangedCallback =
T.Text
-> Bool
-> IO ()
noActionGroupActionEnabledChangedCallback :: Maybe ActionGroupActionEnabledChangedCallback
noActionGroupActionEnabledChangedCallback :: Maybe ActionGroupActionEnabledChangedCallback
noActionGroupActionEnabledChangedCallback = Maybe ActionGroupActionEnabledChangedCallback
forall a. Maybe a
Nothing
type C_ActionGroupActionEnabledChangedCallback =
Ptr () ->
CString ->
CInt ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_ActionGroupActionEnabledChangedCallback :: C_ActionGroupActionEnabledChangedCallback -> IO (FunPtr C_ActionGroupActionEnabledChangedCallback)
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_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'
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
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
type ActionGroupActionRemovedCallback =
T.Text
-> IO ()
noActionGroupActionRemovedCallback :: Maybe ActionGroupActionRemovedCallback
noActionGroupActionRemovedCallback :: Maybe ActionGroupActionAddedCallback
noActionGroupActionRemovedCallback = Maybe ActionGroupActionAddedCallback
forall a. Maybe a
Nothing
type C_ActionGroupActionRemovedCallback =
Ptr () ->
CString ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_ActionGroupActionRemovedCallback :: C_ActionGroupActionRemovedCallback -> IO (FunPtr C_ActionGroupActionRemovedCallback)
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_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'
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
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
type ActionGroupActionStateChangedCallback =
T.Text
-> GVariant
-> IO ()
noActionGroupActionStateChangedCallback :: Maybe ActionGroupActionStateChangedCallback
noActionGroupActionStateChangedCallback :: Maybe ActionGroupActionStateChangedCallback
noActionGroupActionStateChangedCallback = Maybe ActionGroupActionStateChangedCallback
forall a. Maybe a
Nothing
type C_ActionGroupActionStateChangedCallback =
Ptr () ->
CString ->
Ptr GVariant ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_ActionGroupActionStateChangedCallback :: C_ActionGroupActionStateChangedCallback -> IO (FunPtr C_ActionGroupActionStateChangedCallback)
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_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'
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
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
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
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]
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
foreign import ccall "g_action_group_action_added" g_action_group_action_added ::
Ptr ActionGroup ->
CString ->
IO ()
actionGroupActionAdded ::
(B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
a
-> T.Text
-> 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
foreign import ccall "g_action_group_action_enabled_changed" g_action_group_action_enabled_changed ::
Ptr ActionGroup ->
CString ->
CInt ->
IO ()
actionGroupActionEnabledChanged ::
(B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
a
-> T.Text
-> Bool
-> 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
foreign import ccall "g_action_group_action_removed" g_action_group_action_removed ::
Ptr ActionGroup ->
CString ->
IO ()
actionGroupActionRemoved ::
(B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
a
-> T.Text
-> 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
foreign import ccall "g_action_group_action_state_changed" g_action_group_action_state_changed ::
Ptr ActionGroup ->
CString ->
Ptr GVariant ->
IO ()
actionGroupActionStateChanged ::
(B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
a
-> T.Text
-> GVariant
-> 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
foreign import ccall "g_action_group_activate_action" g_action_group_activate_action ::
Ptr ActionGroup ->
CString ->
Ptr GVariant ->
IO ()
actionGroupActivateAction ::
(B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
a
-> T.Text
-> Maybe (GVariant)
-> 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
foreign import ccall "g_action_group_change_action_state" g_action_group_change_action_state ::
Ptr ActionGroup ->
CString ->
Ptr GVariant ->
IO ()
actionGroupChangeActionState ::
(B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
a
-> T.Text
-> GVariant
-> 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
foreign import ccall "g_action_group_get_action_enabled" g_action_group_get_action_enabled ::
Ptr ActionGroup ->
CString ->
IO CInt
actionGroupGetActionEnabled ::
(B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
a
-> T.Text
-> m Bool
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
foreign import ccall "g_action_group_get_action_parameter_type" g_action_group_get_action_parameter_type ::
Ptr ActionGroup ->
CString ->
IO (Ptr GLib.VariantType.VariantType)
actionGroupGetActionParameterType ::
(B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
a
-> T.Text
-> m (Maybe GLib.VariantType.VariantType)
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
foreign import ccall "g_action_group_get_action_state" g_action_group_get_action_state ::
Ptr ActionGroup ->
CString ->
IO (Ptr GVariant)
actionGroupGetActionState ::
(B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
a
-> T.Text
-> m (Maybe GVariant)
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
foreign import ccall "g_action_group_get_action_state_hint" g_action_group_get_action_state_hint ::
Ptr ActionGroup ->
CString ->
IO (Ptr GVariant)
actionGroupGetActionStateHint ::
(B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
a
-> T.Text
-> m (Maybe GVariant)
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
foreign import ccall "g_action_group_get_action_state_type" g_action_group_get_action_state_type ::
Ptr ActionGroup ->
CString ->
IO (Ptr GLib.VariantType.VariantType)
actionGroupGetActionStateType ::
(B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
a
-> T.Text
-> m (Maybe GLib.VariantType.VariantType)
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
foreign import ccall "g_action_group_has_action" g_action_group_has_action ::
Ptr ActionGroup ->
CString ->
IO CInt
actionGroupHasAction ::
(B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
a
-> T.Text
-> m Bool
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
foreign import ccall "g_action_group_list_actions" g_action_group_list_actions ::
Ptr ActionGroup ->
IO (Ptr CString)
actionGroupListActions ::
(B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
a
-> m [T.Text]
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
foreign import ccall "g_action_group_query_action" g_action_group_query_action ::
Ptr ActionGroup ->
CString ->
Ptr CInt ->
Ptr (Ptr GLib.VariantType.VariantType) ->
Ptr (Ptr GLib.VariantType.VariantType) ->
Ptr (Ptr GVariant) ->
Ptr (Ptr GVariant) ->
IO CInt
actionGroupQueryAction ::
(B.CallStack.HasCallStack, MonadIO m, IsActionGroup a) =>
a
-> T.Text
-> m ((Bool, Bool, GLib.VariantType.VariantType, GLib.VariantType.VariantType, GVariant, GVariant))
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