{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The GActionMap interface is implemented by t'GI.Gio.Interfaces.ActionGroup.ActionGroup'
-- implementations that operate by containing a number of
-- named t'GI.Gio.Interfaces.Action.Action' instances, such as t'GI.Gio.Objects.SimpleActionGroup.SimpleActionGroup'.
-- 
-- One useful application of this interface is to map the
-- names of actions from various action groups to unique,
-- prefixed names (e.g. by prepending \"app.\" or \"win.\").
-- This is the motivation for the \'Map\' part of the interface
-- name.
-- 
-- /Since: 2.32/

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

module GI.Gio.Interfaces.ActionMap
    ( 

-- * Exported types
    ActionMap(..)                           ,
    IsActionMap                             ,
    toActionMap                             ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [addAction]("GI.Gio.Interfaces.ActionMap#g:method:addAction"), [addActionEntries]("GI.Gio.Interfaces.ActionMap#g:method:addActionEntries"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [lookupAction]("GI.Gio.Interfaces.ActionMap#g:method:lookupAction"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [removeAction]("GI.Gio.Interfaces.ActionMap#g:method:removeAction"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveActionMapMethod                  ,
#endif

-- ** addAction #method:addAction#

#if defined(ENABLE_OVERLOADING)
    ActionMapAddActionMethodInfo            ,
#endif
    actionMapAddAction                      ,


-- ** addActionEntries #method:addActionEntries#

#if defined(ENABLE_OVERLOADING)
    ActionMapAddActionEntriesMethodInfo     ,
#endif
    actionMapAddActionEntries               ,


-- ** lookupAction #method:lookupAction#

#if defined(ENABLE_OVERLOADING)
    ActionMapLookupActionMethodInfo         ,
#endif
    actionMapLookupAction                   ,


-- ** removeAction #method:removeAction#

#if defined(ENABLE_OVERLOADING)
    ActionMapRemoveActionMethodInfo         ,
#endif
    actionMapRemoveAction                   ,




    ) 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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Action as Gio.Action
import {-# SOURCE #-} qualified GI.Gio.Structs.ActionEntry as Gio.ActionEntry

-- interface ActionMap 
-- | Memory-managed wrapper type.
newtype ActionMap = ActionMap (SP.ManagedPtr ActionMap)
    deriving (ActionMap -> ActionMap -> Bool
(ActionMap -> ActionMap -> Bool)
-> (ActionMap -> ActionMap -> Bool) -> Eq ActionMap
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ActionMap -> ActionMap -> Bool
$c/= :: ActionMap -> ActionMap -> Bool
== :: ActionMap -> ActionMap -> Bool
$c== :: ActionMap -> ActionMap -> Bool
Eq)

instance SP.ManagedPtrNewtype ActionMap where
    toManagedPtr :: ActionMap -> ManagedPtr ActionMap
toManagedPtr (ActionMap ManagedPtr ActionMap
p) = ManagedPtr ActionMap
p

foreign import ccall "g_action_map_get_type"
    c_g_action_map_get_type :: IO B.Types.GType

instance B.Types.TypedObject ActionMap where
    glibType :: IO GType
glibType = IO GType
c_g_action_map_get_type

instance B.Types.GObject ActionMap

-- | Type class for types which can be safely cast to `ActionMap`, for instance with `toActionMap`.
class (SP.GObject o, O.IsDescendantOf ActionMap o) => IsActionMap o
instance (SP.GObject o, O.IsDescendantOf ActionMap o) => IsActionMap o

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

-- | Cast to `ActionMap`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toActionMap :: (MIO.MonadIO m, IsActionMap o) => o -> m ActionMap
toActionMap :: forall (m :: * -> *) o.
(MonadIO m, IsActionMap o) =>
o -> m ActionMap
toActionMap = IO ActionMap -> m ActionMap
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO ActionMap -> m ActionMap)
-> (o -> IO ActionMap) -> o -> m ActionMap
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr ActionMap -> ActionMap) -> o -> IO ActionMap
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr ActionMap -> ActionMap
ActionMap

-- | Convert 'ActionMap' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe ActionMap) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_action_map_get_type
    gvalueSet_ :: Ptr GValue -> Maybe ActionMap -> IO ()
gvalueSet_ Ptr GValue
gv Maybe ActionMap
P.Nothing = Ptr GValue -> Ptr ActionMap -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr ActionMap
forall a. Ptr a
FP.nullPtr :: FP.Ptr ActionMap)
    gvalueSet_ Ptr GValue
gv (P.Just ActionMap
obj) = ActionMap -> (Ptr ActionMap -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ActionMap
obj (Ptr GValue -> Ptr ActionMap -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe ActionMap)
gvalueGet_ Ptr GValue
gv = do
        Ptr ActionMap
ptr <- Ptr GValue -> IO (Ptr ActionMap)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr ActionMap)
        if Ptr ActionMap
ptr Ptr ActionMap -> Ptr ActionMap -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr ActionMap
forall a. Ptr a
FP.nullPtr
        then ActionMap -> Maybe ActionMap
forall a. a -> Maybe a
P.Just (ActionMap -> Maybe ActionMap)
-> IO ActionMap -> IO (Maybe ActionMap)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr ActionMap -> ActionMap)
-> Ptr ActionMap -> IO ActionMap
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr ActionMap -> ActionMap
ActionMap Ptr ActionMap
ptr
        else Maybe ActionMap -> IO (Maybe ActionMap)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ActionMap
forall a. Maybe a
P.Nothing
        
    

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

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveActionMapMethod (t :: Symbol) (o :: *) :: * where
    ResolveActionMapMethod "addAction" o = ActionMapAddActionMethodInfo
    ResolveActionMapMethod "addActionEntries" o = ActionMapAddActionEntriesMethodInfo
    ResolveActionMapMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveActionMapMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveActionMapMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveActionMapMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveActionMapMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveActionMapMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveActionMapMethod "lookupAction" o = ActionMapLookupActionMethodInfo
    ResolveActionMapMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveActionMapMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveActionMapMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveActionMapMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveActionMapMethod "removeAction" o = ActionMapRemoveActionMethodInfo
    ResolveActionMapMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveActionMapMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveActionMapMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveActionMapMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveActionMapMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveActionMapMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveActionMapMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveActionMapMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveActionMapMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveActionMapMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveActionMapMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveActionMapMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveActionMapMethod l o = O.MethodResolutionFailed l o

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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveActionMapMethod t ActionMap, O.OverloadedMethod info ActionMap p, R.HasField t ActionMap p) => R.HasField t ActionMap p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveActionMapMethod t ActionMap, O.OverloadedMethodInfo info ActionMap) => OL.IsLabel t (O.MethodProxy info ActionMap) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- method ActionMap::add_action
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action_map"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ActionMap" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GActionMap" , 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_action_map_add_action" g_action_map_add_action :: 
    Ptr ActionMap ->                        -- action_map : TInterface (Name {namespace = "Gio", name = "ActionMap"})
    Ptr Gio.Action.Action ->                -- action : TInterface (Name {namespace = "Gio", name = "Action"})
    IO ()

-- | Adds an action to the /@actionMap@/.
-- 
-- If the action map already contains an action with the same name
-- as /@action@/ then the old action is dropped from the action map.
-- 
-- The action map takes its own reference on /@action@/.
-- 
-- /Since: 2.32/
actionMapAddAction ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionMap a, Gio.Action.IsAction b) =>
    a
    -- ^ /@actionMap@/: a t'GI.Gio.Interfaces.ActionMap.ActionMap'
    -> b
    -- ^ /@action@/: a t'GI.Gio.Interfaces.Action.Action'
    -> m ()
actionMapAddAction :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsActionMap a, IsAction b) =>
a -> b -> m ()
actionMapAddAction a
actionMap 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 ActionMap
actionMap' <- a -> IO (Ptr ActionMap)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
actionMap
    Ptr Action
action' <- b -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
action
    Ptr ActionMap -> Ptr Action -> IO ()
g_action_map_add_action Ptr ActionMap
actionMap' Ptr Action
action'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
actionMap
    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 ActionMapAddActionMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsActionMap a, Gio.Action.IsAction b) => O.OverloadedMethod ActionMapAddActionMethodInfo a signature where
    overloadedMethod = actionMapAddAction

instance O.OverloadedMethodInfo ActionMapAddActionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.ActionMap.actionMapAddAction",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-ActionMap.html#v:actionMapAddAction"
        }


#endif

-- method ActionMap::add_action_entries
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action_map"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ActionMap" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GActionMap" , 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\n          the first item in 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 if @entries is %NULL-terminated"
--                 , 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 if @entries is %NULL-terminated"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_action_map_add_action_entries" g_action_map_add_action_entries :: 
    Ptr ActionMap ->                        -- action_map : TInterface (Name {namespace = "Gio", name = "ActionMap"})
    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 ()

-- | A convenience function for creating multiple t'GI.Gio.Objects.SimpleAction.SimpleAction' instances
-- and adding them to a t'GI.Gio.Interfaces.ActionMap.ActionMap'.
-- 
-- Each action is constructed as per one t'GI.Gio.Structs.ActionEntry.ActionEntry'.
-- 
-- 
-- === /C code/
-- >
-- >static void
-- >activate_quit (GSimpleAction *simple,
-- >               GVariant      *parameter,
-- >               gpointer       user_data)
-- >{
-- >  exit (0);
-- >}
-- >
-- >static void
-- >activate_print_string (GSimpleAction *simple,
-- >                       GVariant      *parameter,
-- >                       gpointer       user_data)
-- >{
-- >  g_print ("%s\n", g_variant_get_string (parameter, NULL));
-- >}
-- >
-- >static GActionGroup *
-- >create_action_group (void)
-- >{
-- >  const GActionEntry entries[] = {
-- >    { "quit",         activate_quit              },
-- >    { "print-string", activate_print_string, "s" }
-- >  };
-- >  GSimpleActionGroup *group;
-- >
-- >  group = g_simple_action_group_new ();
-- >  g_action_map_add_action_entries (G_ACTION_MAP (group), entries, G_N_ELEMENTS (entries), NULL);
-- >
-- >  return G_ACTION_GROUP (group);
-- >}
-- 
-- 
-- /Since: 2.32/
actionMapAddActionEntries ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionMap a) =>
    a
    -- ^ /@actionMap@/: a t'GI.Gio.Interfaces.ActionMap.ActionMap'
    -> [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 ()
actionMapAddActionEntries :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsActionMap a) =>
a -> [ActionEntry] -> Ptr () -> m ()
actionMapAddActionEntries a
actionMap [ActionEntry]
entries 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
P.length [ActionEntry]
entries
    Ptr ActionMap
actionMap' <- a -> IO (Ptr ActionMap)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
actionMap
    [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 Int
64 [Ptr ActionEntry]
entries'
    Ptr ActionMap -> Ptr ActionEntry -> Int32 -> Ptr () -> IO ()
g_action_map_add_action_entries Ptr ActionMap
actionMap' Ptr ActionEntry
entries'' Int32
nEntries Ptr ()
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
actionMap
    (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 ActionMapAddActionEntriesMethodInfo
instance (signature ~ ([Gio.ActionEntry.ActionEntry] -> Ptr () -> m ()), MonadIO m, IsActionMap a) => O.OverloadedMethod ActionMapAddActionEntriesMethodInfo a signature where
    overloadedMethod = actionMapAddActionEntries

instance O.OverloadedMethodInfo ActionMapAddActionEntriesMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.ActionMap.actionMapAddActionEntries",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-ActionMap.html#v:actionMapAddActionEntries"
        }


#endif

-- method ActionMap::lookup_action
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action_map"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ActionMap" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GActionMap" , 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_action_map_lookup_action" g_action_map_lookup_action :: 
    Ptr ActionMap ->                        -- action_map : TInterface (Name {namespace = "Gio", name = "ActionMap"})
    CString ->                              -- action_name : TBasicType TUTF8
    IO (Ptr Gio.Action.Action)

-- | Looks up the action with the name /@actionName@/ in /@actionMap@/.
-- 
-- If no such action exists, returns 'P.Nothing'.
-- 
-- /Since: 2.32/
actionMapLookupAction ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionMap a) =>
    a
    -- ^ /@actionMap@/: a t'GI.Gio.Interfaces.ActionMap.ActionMap'
    -> T.Text
    -- ^ /@actionName@/: the name of an action
    -> m Gio.Action.Action
    -- ^ __Returns:__ a t'GI.Gio.Interfaces.Action.Action', or 'P.Nothing'
actionMapLookupAction :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsActionMap a) =>
a -> Text -> m Action
actionMapLookupAction a
actionMap 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 ActionMap
actionMap' <- a -> IO (Ptr ActionMap)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
actionMap
    CString
actionName' <- Text -> IO CString
textToCString Text
actionName
    Ptr Action
result <- Ptr ActionMap -> CString -> IO (Ptr Action)
g_action_map_lookup_action Ptr ActionMap
actionMap' CString
actionName'
    Text -> Ptr Action -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"actionMapLookupAction" 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
actionMap
    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 ActionMapLookupActionMethodInfo
instance (signature ~ (T.Text -> m Gio.Action.Action), MonadIO m, IsActionMap a) => O.OverloadedMethod ActionMapLookupActionMethodInfo a signature where
    overloadedMethod = actionMapLookupAction

instance O.OverloadedMethodInfo ActionMapLookupActionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.ActionMap.actionMapLookupAction",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-ActionMap.html#v:actionMapLookupAction"
        }


#endif

-- method ActionMap::remove_action
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action_map"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ActionMap" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GActionMap" , 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_action_map_remove_action" g_action_map_remove_action :: 
    Ptr ActionMap ->                        -- action_map : TInterface (Name {namespace = "Gio", name = "ActionMap"})
    CString ->                              -- action_name : TBasicType TUTF8
    IO ()

-- | Removes the named action from the action map.
-- 
-- If no action of this name is in the map then nothing happens.
-- 
-- /Since: 2.32/
actionMapRemoveAction ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionMap a) =>
    a
    -- ^ /@actionMap@/: a t'GI.Gio.Interfaces.ActionMap.ActionMap'
    -> T.Text
    -- ^ /@actionName@/: the name of the action
    -> m ()
actionMapRemoveAction :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsActionMap a) =>
a -> Text -> m ()
actionMapRemoveAction a
actionMap 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 ActionMap
actionMap' <- a -> IO (Ptr ActionMap)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
actionMap
    CString
actionName' <- Text -> IO CString
textToCString Text
actionName
    Ptr ActionMap -> CString -> IO ()
g_action_map_remove_action Ptr ActionMap
actionMap' CString
actionName'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
actionMap
    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 ActionMapRemoveActionMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsActionMap a) => O.OverloadedMethod ActionMapRemoveActionMethodInfo a signature where
    overloadedMethod = actionMapRemoveAction

instance O.OverloadedMethodInfo ActionMapRemoveActionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.ActionMap.actionMapRemoveAction",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-ActionMap.html#v:actionMapRemoveAction"
        }


#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ActionMap = ActionMapSignalList
type ActionMapSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif