{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gio.Objects.SimpleActionGroup.SimpleActionGroup' is a hash table filled with t'GI.Gio.Interfaces.Action.Action' objects,
-- implementing the t'GI.Gio.Interfaces.ActionGroup.ActionGroup' and t'GI.Gio.Interfaces.ActionMap.ActionMap' interfaces.
-- 
-- /Since: 2.28/

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

module GI.Gio.Objects.SimpleActionGroup
    ( 

-- * Exported types
    SimpleActionGroup(..)                   ,
    IsSimpleActionGroup                     ,
    toSimpleActionGroup                     ,
    noSimpleActionGroup                     ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveSimpleActionGroupMethod          ,
#endif


-- ** addEntries #method:addEntries#

#if defined(ENABLE_OVERLOADING)
    SimpleActionGroupAddEntriesMethodInfo   ,
#endif
    simpleActionGroupAddEntries             ,


-- ** insert #method:insert#

#if defined(ENABLE_OVERLOADING)
    SimpleActionGroupInsertMethodInfo       ,
#endif
    simpleActionGroupInsert                 ,


-- ** lookup #method:lookup#

#if defined(ENABLE_OVERLOADING)
    SimpleActionGroupLookupMethodInfo       ,
#endif
    simpleActionGroupLookup                 ,


-- ** new #method:new#

    simpleActionGroupNew                    ,


-- ** remove #method:remove#

#if defined(ENABLE_OVERLOADING)
    SimpleActionGroupRemoveMethodInfo       ,
#endif
    simpleActionGroupRemove                 ,




    ) 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.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Action as Gio.Action
import {-# SOURCE #-} qualified GI.Gio.Interfaces.ActionGroup as Gio.ActionGroup
import {-# SOURCE #-} qualified GI.Gio.Interfaces.ActionMap as Gio.ActionMap
import {-# SOURCE #-} qualified GI.Gio.Structs.ActionEntry as Gio.ActionEntry

-- | Memory-managed wrapper type.
newtype SimpleActionGroup = SimpleActionGroup (ManagedPtr SimpleActionGroup)
    deriving (SimpleActionGroup -> SimpleActionGroup -> Bool
(SimpleActionGroup -> SimpleActionGroup -> Bool)
-> (SimpleActionGroup -> SimpleActionGroup -> Bool)
-> Eq SimpleActionGroup
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SimpleActionGroup -> SimpleActionGroup -> Bool
$c/= :: SimpleActionGroup -> SimpleActionGroup -> Bool
== :: SimpleActionGroup -> SimpleActionGroup -> Bool
$c== :: SimpleActionGroup -> SimpleActionGroup -> Bool
Eq)
foreign import ccall "g_simple_action_group_get_type"
    c_g_simple_action_group_get_type :: IO GType

instance GObject SimpleActionGroup where
    gobjectType :: IO GType
gobjectType = IO GType
c_g_simple_action_group_get_type
    

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

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

instance O.HasParentTypes SimpleActionGroup
type instance O.ParentTypes SimpleActionGroup = '[GObject.Object.Object, Gio.ActionGroup.ActionGroup, Gio.ActionMap.ActionMap]

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

-- | A convenience alias for `Nothing` :: `Maybe` `SimpleActionGroup`.
noSimpleActionGroup :: Maybe SimpleActionGroup
noSimpleActionGroup :: Maybe SimpleActionGroup
noSimpleActionGroup = Maybe SimpleActionGroup
forall a. Maybe a
Nothing

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

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

#endif

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

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

-- method SimpleActionGroup::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gio" , name = "SimpleActionGroup" })
-- throws : False
-- Skip return : False

foreign import ccall "g_simple_action_group_new" g_simple_action_group_new :: 
    IO (Ptr SimpleActionGroup)

-- | Creates a new, empty, t'GI.Gio.Objects.SimpleActionGroup.SimpleActionGroup'.
-- 
-- /Since: 2.28/
simpleActionGroupNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m SimpleActionGroup
    -- ^ __Returns:__ a new t'GI.Gio.Objects.SimpleActionGroup.SimpleActionGroup'
simpleActionGroupNew :: m SimpleActionGroup
simpleActionGroupNew  = IO SimpleActionGroup -> m SimpleActionGroup
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SimpleActionGroup -> m SimpleActionGroup)
-> IO SimpleActionGroup -> m SimpleActionGroup
forall a b. (a -> b) -> a -> b
$ do
    Ptr SimpleActionGroup
result <- IO (Ptr SimpleActionGroup)
g_simple_action_group_new
    Text -> Ptr SimpleActionGroup -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "simpleActionGroupNew" Ptr SimpleActionGroup
result
    SimpleActionGroup
result' <- ((ManagedPtr SimpleActionGroup -> SimpleActionGroup)
-> Ptr SimpleActionGroup -> IO SimpleActionGroup
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr SimpleActionGroup -> SimpleActionGroup
SimpleActionGroup) Ptr SimpleActionGroup
result
    SimpleActionGroup -> IO SimpleActionGroup
forall (m :: * -> *) a. Monad m => a -> m a
return SimpleActionGroup
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method SimpleActionGroup::add_entries
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "simple"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SimpleActionGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSimpleActionGroup"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "entries"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 2
--                 (TInterface Name { namespace = "Gio" , name = "ActionEntry" })
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a pointer to the first item in\n          an array of #GActionEntry structs"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_entries"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the length of @entries, or -1"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the user data for signal connections"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_entries"
--              , argType = TBasicType TInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the length of @entries, or -1"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_simple_action_group_add_entries" g_simple_action_group_add_entries :: 
    Ptr SimpleActionGroup ->                -- simple : TInterface (Name {namespace = "Gio", name = "SimpleActionGroup"})
    Ptr Gio.ActionEntry.ActionEntry ->      -- entries : TCArray False (-1) 2 (TInterface (Name {namespace = "Gio", name = "ActionEntry"}))
    Int32 ->                                -- n_entries : TBasicType TInt
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

{-# DEPRECATED simpleActionGroupAddEntries ["(Since version 2.38)","Use 'GI.Gio.Interfaces.ActionMap.actionMapAddActionEntries'"] #-}
-- | A convenience function for creating multiple t'GI.Gio.Objects.SimpleAction.SimpleAction' instances
-- and adding them to the action group.
-- 
-- /Since: 2.30/
simpleActionGroupAddEntries ::
    (B.CallStack.HasCallStack, MonadIO m, IsSimpleActionGroup a) =>
    a
    -- ^ /@simple@/: a t'GI.Gio.Objects.SimpleActionGroup.SimpleActionGroup'
    -> [Gio.ActionEntry.ActionEntry]
    -- ^ /@entries@/: a pointer to the first item in
    --           an array of t'GI.Gio.Structs.ActionEntry.ActionEntry' structs
    -> Ptr ()
    -- ^ /@userData@/: the user data for signal connections
    -> m ()
simpleActionGroupAddEntries :: a -> [ActionEntry] -> Ptr () -> m ()
simpleActionGroupAddEntries simple :: a
simple entries :: [ActionEntry]
entries userData :: Ptr ()
userData = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    let nEntries :: Int32
nEntries = Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [ActionEntry] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ActionEntry]
entries
    Ptr SimpleActionGroup
simple' <- a -> IO (Ptr SimpleActionGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
simple
    [Ptr ActionEntry]
entries' <- (ActionEntry -> IO (Ptr ActionEntry))
-> [ActionEntry] -> IO [Ptr ActionEntry]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ActionEntry -> IO (Ptr ActionEntry)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [ActionEntry]
entries
    Ptr ActionEntry
entries'' <- Int -> [Ptr ActionEntry] -> IO (Ptr ActionEntry)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray 64 [Ptr ActionEntry]
entries'
    Ptr SimpleActionGroup
-> Ptr ActionEntry -> Int32 -> Ptr () -> IO ()
g_simple_action_group_add_entries Ptr SimpleActionGroup
simple' Ptr ActionEntry
entries'' Int32
nEntries Ptr ()
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
simple
    (ActionEntry -> IO ()) -> [ActionEntry] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ActionEntry -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [ActionEntry]
entries
    Ptr ActionEntry -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr ActionEntry
entries''
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SimpleActionGroupAddEntriesMethodInfo
instance (signature ~ ([Gio.ActionEntry.ActionEntry] -> Ptr () -> m ()), MonadIO m, IsSimpleActionGroup a) => O.MethodInfo SimpleActionGroupAddEntriesMethodInfo a signature where
    overloadedMethod = simpleActionGroupAddEntries

#endif

-- method SimpleActionGroup::insert
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "simple"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SimpleActionGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSimpleActionGroup"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "action"
--           , argType = TInterface Name { namespace = "Gio" , name = "Action" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAction" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_simple_action_group_insert" g_simple_action_group_insert :: 
    Ptr SimpleActionGroup ->                -- simple : TInterface (Name {namespace = "Gio", name = "SimpleActionGroup"})
    Ptr Gio.Action.Action ->                -- action : TInterface (Name {namespace = "Gio", name = "Action"})
    IO ()

{-# DEPRECATED simpleActionGroupInsert ["(Since version 2.38)","Use 'GI.Gio.Interfaces.ActionMap.actionMapAddAction'"] #-}
-- | Adds an action to the action group.
-- 
-- If the action group already contains an action with the same name as
-- /@action@/ then the old action is dropped from the group.
-- 
-- The action group takes its own reference on /@action@/.
-- 
-- /Since: 2.28/
simpleActionGroupInsert ::
    (B.CallStack.HasCallStack, MonadIO m, IsSimpleActionGroup a, Gio.Action.IsAction b) =>
    a
    -- ^ /@simple@/: a t'GI.Gio.Objects.SimpleActionGroup.SimpleActionGroup'
    -> b
    -- ^ /@action@/: a t'GI.Gio.Interfaces.Action.Action'
    -> m ()
simpleActionGroupInsert :: a -> b -> m ()
simpleActionGroupInsert simple :: a
simple action :: b
action = 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 SimpleActionGroup
simple' <- a -> IO (Ptr SimpleActionGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
simple
    Ptr Action
action' <- b -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
action
    Ptr SimpleActionGroup -> Ptr Action -> IO ()
g_simple_action_group_insert Ptr SimpleActionGroup
simple' Ptr Action
action'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
simple
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
action
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SimpleActionGroupInsertMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsSimpleActionGroup a, Gio.Action.IsAction b) => O.MethodInfo SimpleActionGroupInsertMethodInfo a signature where
    overloadedMethod = simpleActionGroupInsert

#endif

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

foreign import ccall "g_simple_action_group_lookup" g_simple_action_group_lookup :: 
    Ptr SimpleActionGroup ->                -- simple : TInterface (Name {namespace = "Gio", name = "SimpleActionGroup"})
    CString ->                              -- action_name : TBasicType TUTF8
    IO (Ptr Gio.Action.Action)

{-# DEPRECATED simpleActionGroupLookup ["(Since version 2.38)","Use 'GI.Gio.Interfaces.ActionMap.actionMapLookupAction'"] #-}
-- | Looks up the action with the name /@actionName@/ in the group.
-- 
-- If no such action exists, returns 'P.Nothing'.
-- 
-- /Since: 2.28/
simpleActionGroupLookup ::
    (B.CallStack.HasCallStack, MonadIO m, IsSimpleActionGroup a) =>
    a
    -- ^ /@simple@/: a t'GI.Gio.Objects.SimpleActionGroup.SimpleActionGroup'
    -> T.Text
    -- ^ /@actionName@/: the name of an action
    -> m Gio.Action.Action
    -- ^ __Returns:__ a t'GI.Gio.Interfaces.Action.Action', or 'P.Nothing'
simpleActionGroupLookup :: a -> Text -> m Action
simpleActionGroupLookup simple :: a
simple actionName :: Text
actionName = IO Action -> m Action
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Action -> m Action) -> IO Action -> m Action
forall a b. (a -> b) -> a -> b
$ do
    Ptr SimpleActionGroup
simple' <- a -> IO (Ptr SimpleActionGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
simple
    CString
actionName' <- Text -> IO CString
textToCString Text
actionName
    Ptr Action
result <- Ptr SimpleActionGroup -> CString -> IO (Ptr Action)
g_simple_action_group_lookup Ptr SimpleActionGroup
simple' CString
actionName'
    Text -> Ptr Action -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "simpleActionGroupLookup" Ptr Action
result
    Action
result' <- ((ManagedPtr Action -> Action) -> Ptr Action -> IO Action
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Action -> Action
Gio.Action.Action) Ptr Action
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
simple
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
actionName'
    Action -> IO Action
forall (m :: * -> *) a. Monad m => a -> m a
return Action
result'

#if defined(ENABLE_OVERLOADING)
data SimpleActionGroupLookupMethodInfo
instance (signature ~ (T.Text -> m Gio.Action.Action), MonadIO m, IsSimpleActionGroup a) => O.MethodInfo SimpleActionGroupLookupMethodInfo a signature where
    overloadedMethod = simpleActionGroupLookup

#endif

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

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

{-# DEPRECATED simpleActionGroupRemove ["(Since version 2.38)","Use 'GI.Gio.Interfaces.ActionMap.actionMapRemoveAction'"] #-}
-- | Removes the named action from the action group.
-- 
-- If no action of this name is in the group then nothing happens.
-- 
-- /Since: 2.28/
simpleActionGroupRemove ::
    (B.CallStack.HasCallStack, MonadIO m, IsSimpleActionGroup a) =>
    a
    -- ^ /@simple@/: a t'GI.Gio.Objects.SimpleActionGroup.SimpleActionGroup'
    -> T.Text
    -- ^ /@actionName@/: the name of the action
    -> m ()
simpleActionGroupRemove :: a -> Text -> m ()
simpleActionGroupRemove simple :: a
simple 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 SimpleActionGroup
simple' <- a -> IO (Ptr SimpleActionGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
simple
    CString
actionName' <- Text -> IO CString
textToCString Text
actionName
    Ptr SimpleActionGroup -> CString -> IO ()
g_simple_action_group_remove Ptr SimpleActionGroup
simple' CString
actionName'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
simple
    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 SimpleActionGroupRemoveMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsSimpleActionGroup a) => O.MethodInfo SimpleActionGroupRemoveMethodInfo a signature where
    overloadedMethod = simpleActionGroupRemove

#endif