{-# 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.Atk.Interfaces.Action.Action' should be implemented by instances of t'GI.Atk.Objects.Object.Object' classes
-- with which the user can interact directly, i.e. buttons,
-- checkboxes, scrollbars, e.g. components which are not \"passive\"
-- providers of UI information.
-- 
-- Exceptions: when the user interaction is already covered by another
-- appropriate interface such as t'GI.Atk.Interfaces.EditableText.EditableText' (insert\/delete text,
-- etc.) or t'GI.Atk.Interfaces.Value.Value' (set value) then these actions should not be
-- exposed by t'GI.Atk.Interfaces.Action.Action' as well.
-- 
-- Though most UI interactions on components should be invocable via
-- keyboard as well as mouse, there will generally be a close mapping
-- between \"mouse actions\" that are possible on a component and the
-- AtkActions.  Where mouse and keyboard actions are redundant in
-- effect, t'GI.Atk.Interfaces.Action.Action' should expose only one action rather than
-- exposing redundant actions if possible.  By convention we have been
-- using \"mouse centric\" terminology for t'GI.Atk.Interfaces.Action.Action' names.

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

module GI.Atk.Interfaces.Action
    ( 

-- * Exported types
    Action(..)                              ,
    noAction                                ,
    IsAction                                ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveActionMethod                     ,
#endif


-- ** doAction #method:doAction#

#if defined(ENABLE_OVERLOADING)
    ActionDoActionMethodInfo                ,
#endif
    actionDoAction                          ,


-- ** getDescription #method:getDescription#

#if defined(ENABLE_OVERLOADING)
    ActionGetDescriptionMethodInfo          ,
#endif
    actionGetDescription                    ,


-- ** getKeybinding #method:getKeybinding#

#if defined(ENABLE_OVERLOADING)
    ActionGetKeybindingMethodInfo           ,
#endif
    actionGetKeybinding                     ,


-- ** getLocalizedName #method:getLocalizedName#

#if defined(ENABLE_OVERLOADING)
    ActionGetLocalizedNameMethodInfo        ,
#endif
    actionGetLocalizedName                  ,


-- ** getNActions #method:getNActions#

#if defined(ENABLE_OVERLOADING)
    ActionGetNActionsMethodInfo             ,
#endif
    actionGetNActions                       ,


-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    ActionGetNameMethodInfo                 ,
#endif
    actionGetName                           ,


-- ** setDescription #method:setDescription#

#if defined(ENABLE_OVERLOADING)
    ActionSetDescriptionMethodInfo          ,
#endif
    actionSetDescription                    ,




    ) 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


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

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Action = ActionSignalList
type ActionSignalList = ('[ ] :: [(Symbol, *)])

#endif

-- | Type class for types which implement `Action`.
class (ManagedPtrNewtype o, O.IsDescendantOf Action o) => IsAction o
instance (ManagedPtrNewtype o, O.IsDescendantOf Action o) => IsAction o
-- XXX Wrapping a foreign struct/union with no known destructor or size, leak?
instance WrappedPtr Action where
    wrappedPtrCalloc :: IO (Ptr Action)
wrappedPtrCalloc = Ptr Action -> IO (Ptr Action)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Action
forall a. Ptr a
nullPtr
    wrappedPtrCopy :: Action -> IO Action
wrappedPtrCopy = Action -> IO Action
forall (m :: * -> *) a. Monad m => a -> m a
return
    wrappedPtrFree :: Maybe (GDestroyNotify Action)
wrappedPtrFree = Maybe (GDestroyNotify Action)
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
type family ResolveActionMethod (t :: Symbol) (o :: *) :: * where
    ResolveActionMethod "doAction" o = ActionDoActionMethodInfo
    ResolveActionMethod "getDescription" o = ActionGetDescriptionMethodInfo
    ResolveActionMethod "getKeybinding" o = ActionGetKeybindingMethodInfo
    ResolveActionMethod "getLocalizedName" o = ActionGetLocalizedNameMethodInfo
    ResolveActionMethod "getNActions" o = ActionGetNActionsMethodInfo
    ResolveActionMethod "getName" o = ActionGetNameMethodInfo
    ResolveActionMethod "setDescription" o = ActionSetDescriptionMethodInfo
    ResolveActionMethod l o = O.MethodResolutionFailed l o

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

#endif

-- method Action::do_action
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action"
--           , argType = TInterface Name { namespace = "Atk" , name = "Action" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GObject instance that implements AtkActionIface"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "i"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the action index corresponding to the action to be performed"
--                 , 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 "atk_action_do_action" atk_action_do_action :: 
    Ptr Action ->                           -- action : TInterface (Name {namespace = "Atk", name = "Action"})
    Int32 ->                                -- i : TBasicType TInt
    IO CInt

-- | Perform the specified action on the object.
actionDoAction ::
    (B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
    a
    -- ^ /@action@/: a t'GI.GObject.Objects.Object.Object' instance that implements AtkActionIface
    -> Int32
    -- ^ /@i@/: the action index corresponding to the action to be performed
    -> m Bool
    -- ^ __Returns:__ 'P.True' if success, 'P.False' otherwise
actionDoAction :: a -> Int32 -> m Bool
actionDoAction action :: a
action i :: Int32
i = 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 Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
    CInt
result <- Ptr Action -> Int32 -> IO CInt
atk_action_do_action Ptr Action
action' Int32
i
    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
action
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ActionDoActionMethodInfo
instance (signature ~ (Int32 -> m Bool), MonadIO m, IsAction a) => O.MethodInfo ActionDoActionMethodInfo a signature where
    overloadedMethod = actionDoAction

#endif

-- method Action::get_description
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action"
--           , argType = TInterface Name { namespace = "Atk" , name = "Action" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GObject instance that implements AtkActionIface"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "i"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the action index corresponding to the action to be performed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "atk_action_get_description" atk_action_get_description :: 
    Ptr Action ->                           -- action : TInterface (Name {namespace = "Atk", name = "Action"})
    Int32 ->                                -- i : TBasicType TInt
    IO CString

-- | Returns a description of the specified action of the object.
actionGetDescription ::
    (B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
    a
    -- ^ /@action@/: a t'GI.GObject.Objects.Object.Object' instance that implements AtkActionIface
    -> Int32
    -- ^ /@i@/: the action index corresponding to the action to be performed
    -> m (Maybe T.Text)
    -- ^ __Returns:__ a description string, or 'P.Nothing' if /@action@/ does
    -- not implement this interface.
actionGetDescription :: a -> Int32 -> m (Maybe Text)
actionGetDescription action :: a
action i :: Int32
i = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
    CString
result <- Ptr Action -> Int32 -> IO CString
atk_action_get_description Ptr Action
action' Int32
i
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \result' :: CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data ActionGetDescriptionMethodInfo
instance (signature ~ (Int32 -> m (Maybe T.Text)), MonadIO m, IsAction a) => O.MethodInfo ActionGetDescriptionMethodInfo a signature where
    overloadedMethod = actionGetDescription

#endif

-- method Action::get_keybinding
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action"
--           , argType = TInterface Name { namespace = "Atk" , name = "Action" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GObject instance that implements AtkActionIface"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "i"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the action index corresponding to the action to be performed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "atk_action_get_keybinding" atk_action_get_keybinding :: 
    Ptr Action ->                           -- action : TInterface (Name {namespace = "Atk", name = "Action"})
    Int32 ->                                -- i : TBasicType TInt
    IO CString

-- | Gets the keybinding which can be used to activate this action, if one
-- exists. The string returned should contain localized, human-readable,
-- key sequences as they would appear when displayed on screen. It must
-- be in the format \"mnemonic;sequence;shortcut\".
-- 
-- * The mnemonic key activates the object if it is presently enabled onscreen.
-- This typically corresponds to the underlined letter within the widget.
-- Example: \"n\" in a traditional \"New...\" menu item or the \"a\" in \"Apply\" for
-- a button.
-- * The sequence is the full list of keys which invoke the action even if the
-- relevant element is not currently shown on screen. For instance, for a menu
-- item the sequence is the keybindings used to open the parent menus before
-- invoking. The sequence string is colon-delimited. Example: \"Alt+F:N\" in a
-- traditional \"New...\" menu item.
-- * The shortcut, if it exists, will invoke the same action without showing
-- the component or its enclosing menus or dialogs. Example: \"Ctrl+N\" in a
-- traditional \"New...\" menu item.
-- 
-- 
-- Example: For a traditional \"New...\" menu item, the expected return value
-- would be: \"N;Alt+F:N;Ctrl+N\" for the English locale and \"N;Alt+D:N;Strg+N\"
-- for the German locale. If, hypothetically, this menu item lacked a mnemonic,
-- it would be represented by \";;Ctrl+N\" and \";;Strg+N\" respectively.
actionGetKeybinding ::
    (B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
    a
    -- ^ /@action@/: a t'GI.GObject.Objects.Object.Object' instance that implements AtkActionIface
    -> Int32
    -- ^ /@i@/: the action index corresponding to the action to be performed
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the keybinding which can be used to activate
    -- this action, or 'P.Nothing' if there is no keybinding for this action.
actionGetKeybinding :: a -> Int32 -> m (Maybe Text)
actionGetKeybinding action :: a
action i :: Int32
i = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
    CString
result <- Ptr Action -> Int32 -> IO CString
atk_action_get_keybinding Ptr Action
action' Int32
i
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \result' :: CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data ActionGetKeybindingMethodInfo
instance (signature ~ (Int32 -> m (Maybe T.Text)), MonadIO m, IsAction a) => O.MethodInfo ActionGetKeybindingMethodInfo a signature where
    overloadedMethod = actionGetKeybinding

#endif

-- method Action::get_localized_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action"
--           , argType = TInterface Name { namespace = "Atk" , name = "Action" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GObject instance that implements AtkActionIface"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "i"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the action index corresponding to the action to be performed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "atk_action_get_localized_name" atk_action_get_localized_name :: 
    Ptr Action ->                           -- action : TInterface (Name {namespace = "Atk", name = "Action"})
    Int32 ->                                -- i : TBasicType TInt
    IO CString

-- | Returns the localized name of the specified action of the object.
actionGetLocalizedName ::
    (B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
    a
    -- ^ /@action@/: a t'GI.GObject.Objects.Object.Object' instance that implements AtkActionIface
    -> Int32
    -- ^ /@i@/: the action index corresponding to the action to be performed
    -> m (Maybe T.Text)
    -- ^ __Returns:__ a name string, or 'P.Nothing' if /@action@/ does not
    -- implement this interface.
actionGetLocalizedName :: a -> Int32 -> m (Maybe Text)
actionGetLocalizedName action :: a
action i :: Int32
i = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
    CString
result <- Ptr Action -> Int32 -> IO CString
atk_action_get_localized_name Ptr Action
action' Int32
i
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \result' :: CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data ActionGetLocalizedNameMethodInfo
instance (signature ~ (Int32 -> m (Maybe T.Text)), MonadIO m, IsAction a) => O.MethodInfo ActionGetLocalizedNameMethodInfo a signature where
    overloadedMethod = actionGetLocalizedName

#endif

-- method Action::get_n_actions
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action"
--           , argType = TInterface Name { namespace = "Atk" , name = "Action" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GObject instance that implements AtkActionIface"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "atk_action_get_n_actions" atk_action_get_n_actions :: 
    Ptr Action ->                           -- action : TInterface (Name {namespace = "Atk", name = "Action"})
    IO Int32

-- | Gets the number of accessible actions available on the object.
-- If there are more than one, the first one is considered the
-- \"default\" action of the object.
actionGetNActions ::
    (B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
    a
    -- ^ /@action@/: a t'GI.GObject.Objects.Object.Object' instance that implements AtkActionIface
    -> m Int32
    -- ^ __Returns:__ a the number of actions, or 0 if /@action@/ does not
    -- implement this interface.
actionGetNActions :: a -> m Int32
actionGetNActions action :: a
action = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
    Int32
result <- Ptr Action -> IO Int32
atk_action_get_n_actions Ptr Action
action'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data ActionGetNActionsMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsAction a) => O.MethodInfo ActionGetNActionsMethodInfo a signature where
    overloadedMethod = actionGetNActions

#endif

-- method Action::get_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action"
--           , argType = TInterface Name { namespace = "Atk" , name = "Action" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GObject instance that implements AtkActionIface"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "i"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the action index corresponding to the action to be performed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "atk_action_get_name" atk_action_get_name :: 
    Ptr Action ->                           -- action : TInterface (Name {namespace = "Atk", name = "Action"})
    Int32 ->                                -- i : TBasicType TInt
    IO CString

-- | Returns a non-localized string naming the specified action of the
-- object. This name is generally not descriptive of the end result
-- of the action, but instead names the \'interaction type\' which the
-- object supports. By convention, the above strings should be used to
-- represent the actions which correspond to the common point-and-click
-- interaction techniques of the same name: i.e.
-- \"click\", \"press\", \"release\", \"drag\", \"drop\", \"popup\", etc.
-- The \"popup\" action should be used to pop up a context menu for the
-- object, if one exists.
-- 
-- For technical reasons, some toolkits cannot guarantee that the
-- reported action is actually \'bound\' to a nontrivial user event;
-- i.e. the result of some actions via 'GI.Atk.Interfaces.Action.actionDoAction' may be
-- NIL.
actionGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
    a
    -- ^ /@action@/: a t'GI.GObject.Objects.Object.Object' instance that implements AtkActionIface
    -> Int32
    -- ^ /@i@/: the action index corresponding to the action to be performed
    -> m (Maybe T.Text)
    -- ^ __Returns:__ a name string, or 'P.Nothing' if /@action@/ does not
    -- implement this interface.
actionGetName :: a -> Int32 -> m (Maybe Text)
actionGetName action :: a
action i :: Int32
i = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
    CString
result <- Ptr Action -> Int32 -> IO CString
atk_action_get_name Ptr Action
action' Int32
i
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \result' :: CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data ActionGetNameMethodInfo
instance (signature ~ (Int32 -> m (Maybe T.Text)), MonadIO m, IsAction a) => O.MethodInfo ActionGetNameMethodInfo a signature where
    overloadedMethod = actionGetName

#endif

-- method Action::set_description
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action"
--           , argType = TInterface Name { namespace = "Atk" , name = "Action" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GObject instance that implements AtkActionIface"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "i"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the action index corresponding to the action to be performed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "desc"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the description to be assigned to this action"
--                 , 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 "atk_action_set_description" atk_action_set_description :: 
    Ptr Action ->                           -- action : TInterface (Name {namespace = "Atk", name = "Action"})
    Int32 ->                                -- i : TBasicType TInt
    CString ->                              -- desc : TBasicType TUTF8
    IO CInt

-- | Sets a description of the specified action of the object.
actionSetDescription ::
    (B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
    a
    -- ^ /@action@/: a t'GI.GObject.Objects.Object.Object' instance that implements AtkActionIface
    -> Int32
    -- ^ /@i@/: the action index corresponding to the action to be performed
    -> T.Text
    -- ^ /@desc@/: the description to be assigned to this action
    -> m Bool
    -- ^ __Returns:__ a gboolean representing if the description was successfully set;
actionSetDescription :: a -> Int32 -> Text -> m Bool
actionSetDescription action :: a
action i :: Int32
i desc :: Text
desc = 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 Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
    CString
desc' <- Text -> IO CString
textToCString Text
desc
    CInt
result <- Ptr Action -> Int32 -> CString -> IO CInt
atk_action_set_description Ptr Action
action' Int32
i CString
desc'
    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
action
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
desc'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ActionSetDescriptionMethodInfo
instance (signature ~ (Int32 -> T.Text -> m Bool), MonadIO m, IsAction a) => O.MethodInfo ActionSetDescriptionMethodInfo a signature where
    overloadedMethod = actionSetDescription

#endif