{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GtkShortcutController@ is an event controller that manages shortcuts.
-- 
-- Most common shortcuts are using this controller implicitly, e.g. by
-- adding a mnemonic underline to a @GtkLabel@, or by installing a key
-- binding using t'GI.Gtk.Structs.WidgetClass.WidgetClass'.@/add_binding/@(), or by adding accelerators
-- to global actions using 'GI.Gtk.Objects.Application.applicationSetAccelsForAction'.
-- 
-- But it is possible to create your own shortcut controller, and add
-- shortcuts to it.
-- 
-- @GtkShortcutController@ implements @GListModel@ for querying the
-- shortcuts that have been added to it.
-- 
-- = GtkShortcutController as a GtkBuildable
-- 
-- @GtkShortcutControllers@ can be creates in ui files to set up
-- shortcuts in the same place as the widgets.
-- 
-- An example of a UI definition fragment with @GtkShortcutController@:
-- 
-- === /xml code/
-- >  <object class='GtkButton'>
-- >    <child>
-- >      <object class='GtkShortcutController'>
-- >        <property name='scope'>managed</property>
-- >        <child>
-- >          <object class='GtkShortcut'>
-- >            <property name='trigger'>&lt;Control&gt;k</property>
-- >            <property name='action'>activate</property>
-- >          </object>
-- >        </child>
-- >      </object>
-- >    </child>
-- >  </object>
-- 
-- 
-- This example creates a t'GI.Gtk.Objects.ActivateAction.ActivateAction' for triggering the
-- @activate@ signal of the @GtkButton@. See 'GI.Gtk.Objects.ShortcutAction.shortcutActionParseString'
-- for the syntax for other kinds of @GtkShortcutAction@. See
-- 'GI.Gtk.Objects.ShortcutTrigger.shortcutTriggerParseString' to learn more about the syntax
-- for triggers.

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

module GI.Gtk.Objects.ShortcutController
    ( 

-- * Exported types
    ShortcutController(..)                  ,
    IsShortcutController                    ,
    toShortcutController                    ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [addShortcut]("GI.Gtk.Objects.ShortcutController#g:method:addShortcut"), [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"), [itemsChanged]("GI.Gio.Interfaces.ListModel#g:method:itemsChanged"), [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"), [removeShortcut]("GI.Gtk.Objects.ShortcutController#g:method:removeShortcut"), [reset]("GI.Gtk.Objects.EventController#g:method:reset"), [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
-- [getBuildableId]("GI.Gtk.Interfaces.Buildable#g:method:getBuildableId"), [getCurrentEvent]("GI.Gtk.Objects.EventController#g:method:getCurrentEvent"), [getCurrentEventDevice]("GI.Gtk.Objects.EventController#g:method:getCurrentEventDevice"), [getCurrentEventState]("GI.Gtk.Objects.EventController#g:method:getCurrentEventState"), [getCurrentEventTime]("GI.Gtk.Objects.EventController#g:method:getCurrentEventTime"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getItem]("GI.Gio.Interfaces.ListModel#g:method:getItem"), [getItemType]("GI.Gio.Interfaces.ListModel#g:method:getItemType"), [getMnemonicsModifiers]("GI.Gtk.Objects.ShortcutController#g:method:getMnemonicsModifiers"), [getNItems]("GI.Gio.Interfaces.ListModel#g:method:getNItems"), [getName]("GI.Gtk.Objects.EventController#g:method:getName"), [getPropagationLimit]("GI.Gtk.Objects.EventController#g:method:getPropagationLimit"), [getPropagationPhase]("GI.Gtk.Objects.EventController#g:method:getPropagationPhase"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getScope]("GI.Gtk.Objects.ShortcutController#g:method:getScope"), [getWidget]("GI.Gtk.Objects.EventController#g:method:getWidget").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setMnemonicsModifiers]("GI.Gtk.Objects.ShortcutController#g:method:setMnemonicsModifiers"), [setName]("GI.Gtk.Objects.EventController#g:method:setName"), [setPropagationLimit]("GI.Gtk.Objects.EventController#g:method:setPropagationLimit"), [setPropagationPhase]("GI.Gtk.Objects.EventController#g:method:setPropagationPhase"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setScope]("GI.Gtk.Objects.ShortcutController#g:method:setScope"), [setStaticName]("GI.Gtk.Objects.EventController#g:method:setStaticName").

#if defined(ENABLE_OVERLOADING)
    ResolveShortcutControllerMethod         ,
#endif

-- ** addShortcut #method:addShortcut#

#if defined(ENABLE_OVERLOADING)
    ShortcutControllerAddShortcutMethodInfo ,
#endif
    shortcutControllerAddShortcut           ,


-- ** getMnemonicsModifiers #method:getMnemonicsModifiers#

#if defined(ENABLE_OVERLOADING)
    ShortcutControllerGetMnemonicsModifiersMethodInfo,
#endif
    shortcutControllerGetMnemonicsModifiers ,


-- ** getScope #method:getScope#

#if defined(ENABLE_OVERLOADING)
    ShortcutControllerGetScopeMethodInfo    ,
#endif
    shortcutControllerGetScope              ,


-- ** new #method:new#

    shortcutControllerNew                   ,


-- ** newForModel #method:newForModel#

    shortcutControllerNewForModel           ,


-- ** removeShortcut #method:removeShortcut#

#if defined(ENABLE_OVERLOADING)
    ShortcutControllerRemoveShortcutMethodInfo,
#endif
    shortcutControllerRemoveShortcut        ,


-- ** setMnemonicsModifiers #method:setMnemonicsModifiers#

#if defined(ENABLE_OVERLOADING)
    ShortcutControllerSetMnemonicsModifiersMethodInfo,
#endif
    shortcutControllerSetMnemonicsModifiers ,


-- ** setScope #method:setScope#

#if defined(ENABLE_OVERLOADING)
    ShortcutControllerSetScopeMethodInfo    ,
#endif
    shortcutControllerSetScope              ,




 -- * Properties


-- ** itemType #attr:itemType#
-- | The type of items. See 'GI.Gio.Interfaces.ListModel.listModelGetItemType'.
-- 
-- /Since: 4.8/

#if defined(ENABLE_OVERLOADING)
    ShortcutControllerItemTypePropertyInfo  ,
#endif
    getShortcutControllerItemType           ,
#if defined(ENABLE_OVERLOADING)
    shortcutControllerItemType              ,
#endif


-- ** mnemonicModifiers #attr:mnemonicModifiers#
-- | The modifiers that need to be pressed to allow mnemonics activation.

#if defined(ENABLE_OVERLOADING)
    ShortcutControllerMnemonicModifiersPropertyInfo,
#endif
    constructShortcutControllerMnemonicModifiers,
    getShortcutControllerMnemonicModifiers  ,
    setShortcutControllerMnemonicModifiers  ,
#if defined(ENABLE_OVERLOADING)
    shortcutControllerMnemonicModifiers     ,
#endif


-- ** model #attr:model#
-- | A list model to take shortcuts from.

#if defined(ENABLE_OVERLOADING)
    ShortcutControllerModelPropertyInfo     ,
#endif
    constructShortcutControllerModel        ,
#if defined(ENABLE_OVERLOADING)
    shortcutControllerModel                 ,
#endif


-- ** nItems #attr:nItems#
-- | The number of items. See 'GI.Gio.Interfaces.ListModel.listModelGetNItems'.
-- 
-- /Since: 4.8/

#if defined(ENABLE_OVERLOADING)
    ShortcutControllerNItemsPropertyInfo    ,
#endif
    getShortcutControllerNItems             ,
#if defined(ENABLE_OVERLOADING)
    shortcutControllerNItems                ,
#endif


-- ** scope #attr:scope#
-- | What scope the shortcuts will be handled in.

#if defined(ENABLE_OVERLOADING)
    ShortcutControllerScopePropertyInfo     ,
#endif
    constructShortcutControllerScope        ,
    getShortcutControllerScope              ,
    setShortcutControllerScope              ,
#if defined(ENABLE_OVERLOADING)
    shortcutControllerScope                 ,
#endif




    ) 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.GHashTable as B.GHT
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.Coerce as Coerce
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 qualified GI.Gdk.Flags as Gdk.Flags
import qualified GI.Gio.Interfaces.ListModel as Gio.ListModel
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Objects.EventController as Gtk.EventController
import {-# SOURCE #-} qualified GI.Gtk.Objects.Shortcut as Gtk.Shortcut

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

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

foreign import ccall "gtk_shortcut_controller_get_type"
    c_gtk_shortcut_controller_get_type :: IO B.Types.GType

instance B.Types.TypedObject ShortcutController where
    glibType :: IO GType
glibType = IO GType
c_gtk_shortcut_controller_get_type

instance B.Types.GObject ShortcutController

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

instance O.HasParentTypes ShortcutController
type instance O.ParentTypes ShortcutController = '[Gtk.EventController.EventController, GObject.Object.Object, Gio.ListModel.ListModel, Gtk.Buildable.Buildable]

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

-- | Convert 'ShortcutController' 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 ShortcutController) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_shortcut_controller_get_type
    gvalueSet_ :: Ptr GValue -> Maybe ShortcutController -> IO ()
gvalueSet_ Ptr GValue
gv Maybe ShortcutController
P.Nothing = Ptr GValue -> Ptr ShortcutController -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr ShortcutController
forall a. Ptr a
FP.nullPtr :: FP.Ptr ShortcutController)
    gvalueSet_ Ptr GValue
gv (P.Just ShortcutController
obj) = ShortcutController -> (Ptr ShortcutController -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ShortcutController
obj (Ptr GValue -> Ptr ShortcutController -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe ShortcutController)
gvalueGet_ Ptr GValue
gv = do
        Ptr ShortcutController
ptr <- Ptr GValue -> IO (Ptr ShortcutController)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr ShortcutController)
        if Ptr ShortcutController
ptr Ptr ShortcutController -> Ptr ShortcutController -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr ShortcutController
forall a. Ptr a
FP.nullPtr
        then ShortcutController -> Maybe ShortcutController
forall a. a -> Maybe a
P.Just (ShortcutController -> Maybe ShortcutController)
-> IO ShortcutController -> IO (Maybe ShortcutController)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr ShortcutController -> ShortcutController)
-> Ptr ShortcutController -> IO ShortcutController
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr ShortcutController -> ShortcutController
ShortcutController Ptr ShortcutController
ptr
        else Maybe ShortcutController -> IO (Maybe ShortcutController)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ShortcutController
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveShortcutControllerMethod (t :: Symbol) (o :: *) :: * where
    ResolveShortcutControllerMethod "addShortcut" o = ShortcutControllerAddShortcutMethodInfo
    ResolveShortcutControllerMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveShortcutControllerMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveShortcutControllerMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveShortcutControllerMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveShortcutControllerMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveShortcutControllerMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveShortcutControllerMethod "itemsChanged" o = Gio.ListModel.ListModelItemsChangedMethodInfo
    ResolveShortcutControllerMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveShortcutControllerMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveShortcutControllerMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveShortcutControllerMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveShortcutControllerMethod "removeShortcut" o = ShortcutControllerRemoveShortcutMethodInfo
    ResolveShortcutControllerMethod "reset" o = Gtk.EventController.EventControllerResetMethodInfo
    ResolveShortcutControllerMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveShortcutControllerMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveShortcutControllerMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveShortcutControllerMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveShortcutControllerMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveShortcutControllerMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveShortcutControllerMethod "getBuildableId" o = Gtk.Buildable.BuildableGetBuildableIdMethodInfo
    ResolveShortcutControllerMethod "getCurrentEvent" o = Gtk.EventController.EventControllerGetCurrentEventMethodInfo
    ResolveShortcutControllerMethod "getCurrentEventDevice" o = Gtk.EventController.EventControllerGetCurrentEventDeviceMethodInfo
    ResolveShortcutControllerMethod "getCurrentEventState" o = Gtk.EventController.EventControllerGetCurrentEventStateMethodInfo
    ResolveShortcutControllerMethod "getCurrentEventTime" o = Gtk.EventController.EventControllerGetCurrentEventTimeMethodInfo
    ResolveShortcutControllerMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveShortcutControllerMethod "getItem" o = Gio.ListModel.ListModelGetItemMethodInfo
    ResolveShortcutControllerMethod "getItemType" o = Gio.ListModel.ListModelGetItemTypeMethodInfo
    ResolveShortcutControllerMethod "getMnemonicsModifiers" o = ShortcutControllerGetMnemonicsModifiersMethodInfo
    ResolveShortcutControllerMethod "getNItems" o = Gio.ListModel.ListModelGetNItemsMethodInfo
    ResolveShortcutControllerMethod "getName" o = Gtk.EventController.EventControllerGetNameMethodInfo
    ResolveShortcutControllerMethod "getPropagationLimit" o = Gtk.EventController.EventControllerGetPropagationLimitMethodInfo
    ResolveShortcutControllerMethod "getPropagationPhase" o = Gtk.EventController.EventControllerGetPropagationPhaseMethodInfo
    ResolveShortcutControllerMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveShortcutControllerMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveShortcutControllerMethod "getScope" o = ShortcutControllerGetScopeMethodInfo
    ResolveShortcutControllerMethod "getWidget" o = Gtk.EventController.EventControllerGetWidgetMethodInfo
    ResolveShortcutControllerMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveShortcutControllerMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveShortcutControllerMethod "setMnemonicsModifiers" o = ShortcutControllerSetMnemonicsModifiersMethodInfo
    ResolveShortcutControllerMethod "setName" o = Gtk.EventController.EventControllerSetNameMethodInfo
    ResolveShortcutControllerMethod "setPropagationLimit" o = Gtk.EventController.EventControllerSetPropagationLimitMethodInfo
    ResolveShortcutControllerMethod "setPropagationPhase" o = Gtk.EventController.EventControllerSetPropagationPhaseMethodInfo
    ResolveShortcutControllerMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveShortcutControllerMethod "setScope" o = ShortcutControllerSetScopeMethodInfo
    ResolveShortcutControllerMethod "setStaticName" o = Gtk.EventController.EventControllerSetStaticNameMethodInfo
    ResolveShortcutControllerMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveShortcutControllerMethod t ShortcutController, O.OverloadedMethod info ShortcutController p) => OL.IsLabel t (ShortcutController -> 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 ~ ResolveShortcutControllerMethod t ShortcutController, O.OverloadedMethod info ShortcutController p, R.HasField t ShortcutController p) => R.HasField t ShortcutController p where
    getField = O.overloadedMethod @info

#endif

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

#endif

-- VVV Prop "item-type"
   -- Type: TBasicType TGType
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@item-type@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' shortcutController #itemType
-- @
getShortcutControllerItemType :: (MonadIO m, IsShortcutController o) => o -> m GType
getShortcutControllerItemType :: forall (m :: * -> *) o.
(MonadIO m, IsShortcutController o) =>
o -> m GType
getShortcutControllerItemType o
obj = IO GType -> m GType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO GType -> m GType) -> IO GType -> m GType
forall a b. (a -> b) -> a -> b
$ o -> String -> IO GType
forall a. GObject a => a -> String -> IO GType
B.Properties.getObjectPropertyGType o
obj String
"item-type"

#if defined(ENABLE_OVERLOADING)
data ShortcutControllerItemTypePropertyInfo
instance AttrInfo ShortcutControllerItemTypePropertyInfo where
    type AttrAllowedOps ShortcutControllerItemTypePropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint ShortcutControllerItemTypePropertyInfo = IsShortcutController
    type AttrSetTypeConstraint ShortcutControllerItemTypePropertyInfo = (~) ()
    type AttrTransferTypeConstraint ShortcutControllerItemTypePropertyInfo = (~) ()
    type AttrTransferType ShortcutControllerItemTypePropertyInfo = ()
    type AttrGetType ShortcutControllerItemTypePropertyInfo = GType
    type AttrLabel ShortcutControllerItemTypePropertyInfo = "item-type"
    type AttrOrigin ShortcutControllerItemTypePropertyInfo = ShortcutController
    attrGet = getShortcutControllerItemType
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ShortcutController.itemType"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-ShortcutController.html#g:attr:itemType"
        })
#endif

-- VVV Prop "mnemonic-modifiers"
   -- Type: TInterface (Name {namespace = "Gdk", name = "ModifierType"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@mnemonic-modifiers@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' shortcutController #mnemonicModifiers
-- @
getShortcutControllerMnemonicModifiers :: (MonadIO m, IsShortcutController o) => o -> m [Gdk.Flags.ModifierType]
getShortcutControllerMnemonicModifiers :: forall (m :: * -> *) o.
(MonadIO m, IsShortcutController o) =>
o -> m [ModifierType]
getShortcutControllerMnemonicModifiers o
obj = IO [ModifierType] -> m [ModifierType]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO [ModifierType] -> m [ModifierType])
-> IO [ModifierType] -> m [ModifierType]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO [ModifierType]
forall a b.
(GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
B.Properties.getObjectPropertyFlags o
obj String
"mnemonic-modifiers"

-- | Set the value of the “@mnemonic-modifiers@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' shortcutController [ #mnemonicModifiers 'Data.GI.Base.Attributes.:=' value ]
-- @
setShortcutControllerMnemonicModifiers :: (MonadIO m, IsShortcutController o) => o -> [Gdk.Flags.ModifierType] -> m ()
setShortcutControllerMnemonicModifiers :: forall (m :: * -> *) o.
(MonadIO m, IsShortcutController o) =>
o -> [ModifierType] -> m ()
setShortcutControllerMnemonicModifiers o
obj [ModifierType]
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> [ModifierType] -> IO ()
forall a b.
(IsGFlag b, BoxedFlags b, GObject a) =>
a -> String -> [b] -> IO ()
B.Properties.setObjectPropertyFlags o
obj String
"mnemonic-modifiers" [ModifierType]
val

-- | Construct a `GValueConstruct` with valid value for the “@mnemonic-modifiers@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructShortcutControllerMnemonicModifiers :: (IsShortcutController o, MIO.MonadIO m) => [Gdk.Flags.ModifierType] -> m (GValueConstruct o)
constructShortcutControllerMnemonicModifiers :: forall o (m :: * -> *).
(IsShortcutController o, MonadIO m) =>
[ModifierType] -> m (GValueConstruct o)
constructShortcutControllerMnemonicModifiers [ModifierType]
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> [ModifierType] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags String
"mnemonic-modifiers" [ModifierType]
val

#if defined(ENABLE_OVERLOADING)
data ShortcutControllerMnemonicModifiersPropertyInfo
instance AttrInfo ShortcutControllerMnemonicModifiersPropertyInfo where
    type AttrAllowedOps ShortcutControllerMnemonicModifiersPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ShortcutControllerMnemonicModifiersPropertyInfo = IsShortcutController
    type AttrSetTypeConstraint ShortcutControllerMnemonicModifiersPropertyInfo = (~) [Gdk.Flags.ModifierType]
    type AttrTransferTypeConstraint ShortcutControllerMnemonicModifiersPropertyInfo = (~) [Gdk.Flags.ModifierType]
    type AttrTransferType ShortcutControllerMnemonicModifiersPropertyInfo = [Gdk.Flags.ModifierType]
    type AttrGetType ShortcutControllerMnemonicModifiersPropertyInfo = [Gdk.Flags.ModifierType]
    type AttrLabel ShortcutControllerMnemonicModifiersPropertyInfo = "mnemonic-modifiers"
    type AttrOrigin ShortcutControllerMnemonicModifiersPropertyInfo = ShortcutController
    attrGet = getShortcutControllerMnemonicModifiers
    attrSet = setShortcutControllerMnemonicModifiers
    attrTransfer _ v = do
        return v
    attrConstruct = constructShortcutControllerMnemonicModifiers
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ShortcutController.mnemonicModifiers"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-ShortcutController.html#g:attr:mnemonicModifiers"
        })
#endif

-- VVV Prop "model"
   -- Type: TInterface (Name {namespace = "Gio", name = "ListModel"})
   -- Flags: [PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Construct a `GValueConstruct` with valid value for the “@model@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructShortcutControllerModel :: (IsShortcutController o, MIO.MonadIO m, Gio.ListModel.IsListModel a) => a -> m (GValueConstruct o)
constructShortcutControllerModel :: forall o (m :: * -> *) a.
(IsShortcutController o, MonadIO m, IsListModel a) =>
a -> m (GValueConstruct o)
constructShortcutControllerModel a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"model" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data ShortcutControllerModelPropertyInfo
instance AttrInfo ShortcutControllerModelPropertyInfo where
    type AttrAllowedOps ShortcutControllerModelPropertyInfo = '[ 'AttrConstruct, 'AttrClear]
    type AttrBaseTypeConstraint ShortcutControllerModelPropertyInfo = IsShortcutController
    type AttrSetTypeConstraint ShortcutControllerModelPropertyInfo = Gio.ListModel.IsListModel
    type AttrTransferTypeConstraint ShortcutControllerModelPropertyInfo = Gio.ListModel.IsListModel
    type AttrTransferType ShortcutControllerModelPropertyInfo = Gio.ListModel.ListModel
    type AttrGetType ShortcutControllerModelPropertyInfo = ()
    type AttrLabel ShortcutControllerModelPropertyInfo = "model"
    type AttrOrigin ShortcutControllerModelPropertyInfo = ShortcutController
    attrGet = undefined
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gio.ListModel.ListModel v
    attrConstruct = constructShortcutControllerModel
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ShortcutController.model"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-ShortcutController.html#g:attr:model"
        })
#endif

-- VVV Prop "n-items"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@n-items@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' shortcutController #nItems
-- @
getShortcutControllerNItems :: (MonadIO m, IsShortcutController o) => o -> m Word32
getShortcutControllerNItems :: forall (m :: * -> *) o.
(MonadIO m, IsShortcutController o) =>
o -> m Word32
getShortcutControllerNItems o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"n-items"

#if defined(ENABLE_OVERLOADING)
data ShortcutControllerNItemsPropertyInfo
instance AttrInfo ShortcutControllerNItemsPropertyInfo where
    type AttrAllowedOps ShortcutControllerNItemsPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint ShortcutControllerNItemsPropertyInfo = IsShortcutController
    type AttrSetTypeConstraint ShortcutControllerNItemsPropertyInfo = (~) ()
    type AttrTransferTypeConstraint ShortcutControllerNItemsPropertyInfo = (~) ()
    type AttrTransferType ShortcutControllerNItemsPropertyInfo = ()
    type AttrGetType ShortcutControllerNItemsPropertyInfo = Word32
    type AttrLabel ShortcutControllerNItemsPropertyInfo = "n-items"
    type AttrOrigin ShortcutControllerNItemsPropertyInfo = ShortcutController
    attrGet = getShortcutControllerNItems
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ShortcutController.nItems"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-ShortcutController.html#g:attr:nItems"
        })
#endif

-- VVV Prop "scope"
   -- Type: TInterface (Name {namespace = "Gtk", name = "ShortcutScope"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@scope@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' shortcutController #scope
-- @
getShortcutControllerScope :: (MonadIO m, IsShortcutController o) => o -> m Gtk.Enums.ShortcutScope
getShortcutControllerScope :: forall (m :: * -> *) o.
(MonadIO m, IsShortcutController o) =>
o -> m ShortcutScope
getShortcutControllerScope o
obj = IO ShortcutScope -> m ShortcutScope
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO ShortcutScope -> m ShortcutScope)
-> IO ShortcutScope -> m ShortcutScope
forall a b. (a -> b) -> a -> b
$ o -> String -> IO ShortcutScope
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"scope"

-- | Set the value of the “@scope@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' shortcutController [ #scope 'Data.GI.Base.Attributes.:=' value ]
-- @
setShortcutControllerScope :: (MonadIO m, IsShortcutController o) => o -> Gtk.Enums.ShortcutScope -> m ()
setShortcutControllerScope :: forall (m :: * -> *) o.
(MonadIO m, IsShortcutController o) =>
o -> ShortcutScope -> m ()
setShortcutControllerScope o
obj ShortcutScope
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> ShortcutScope -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"scope" ShortcutScope
val

-- | Construct a `GValueConstruct` with valid value for the “@scope@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructShortcutControllerScope :: (IsShortcutController o, MIO.MonadIO m) => Gtk.Enums.ShortcutScope -> m (GValueConstruct o)
constructShortcutControllerScope :: forall o (m :: * -> *).
(IsShortcutController o, MonadIO m) =>
ShortcutScope -> m (GValueConstruct o)
constructShortcutControllerScope ShortcutScope
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> ShortcutScope -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"scope" ShortcutScope
val

#if defined(ENABLE_OVERLOADING)
data ShortcutControllerScopePropertyInfo
instance AttrInfo ShortcutControllerScopePropertyInfo where
    type AttrAllowedOps ShortcutControllerScopePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ShortcutControllerScopePropertyInfo = IsShortcutController
    type AttrSetTypeConstraint ShortcutControllerScopePropertyInfo = (~) Gtk.Enums.ShortcutScope
    type AttrTransferTypeConstraint ShortcutControllerScopePropertyInfo = (~) Gtk.Enums.ShortcutScope
    type AttrTransferType ShortcutControllerScopePropertyInfo = Gtk.Enums.ShortcutScope
    type AttrGetType ShortcutControllerScopePropertyInfo = Gtk.Enums.ShortcutScope
    type AttrLabel ShortcutControllerScopePropertyInfo = "scope"
    type AttrOrigin ShortcutControllerScopePropertyInfo = ShortcutController
    attrGet = getShortcutControllerScope
    attrSet = setShortcutControllerScope
    attrTransfer _ v = do
        return v
    attrConstruct = constructShortcutControllerScope
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ShortcutController.scope"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-ShortcutController.html#g:attr:scope"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ShortcutController
type instance O.AttributeList ShortcutController = ShortcutControllerAttributeList
type ShortcutControllerAttributeList = ('[ '("itemType", ShortcutControllerItemTypePropertyInfo), '("mnemonicModifiers", ShortcutControllerMnemonicModifiersPropertyInfo), '("model", ShortcutControllerModelPropertyInfo), '("nItems", ShortcutControllerNItemsPropertyInfo), '("name", Gtk.EventController.EventControllerNamePropertyInfo), '("propagationLimit", Gtk.EventController.EventControllerPropagationLimitPropertyInfo), '("propagationPhase", Gtk.EventController.EventControllerPropagationPhasePropertyInfo), '("scope", ShortcutControllerScopePropertyInfo), '("widget", Gtk.EventController.EventControllerWidgetPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
shortcutControllerItemType :: AttrLabelProxy "itemType"
shortcutControllerItemType = AttrLabelProxy

shortcutControllerMnemonicModifiers :: AttrLabelProxy "mnemonicModifiers"
shortcutControllerMnemonicModifiers = AttrLabelProxy

shortcutControllerModel :: AttrLabelProxy "model"
shortcutControllerModel = AttrLabelProxy

shortcutControllerNItems :: AttrLabelProxy "nItems"
shortcutControllerNItems = AttrLabelProxy

shortcutControllerScope :: AttrLabelProxy "scope"
shortcutControllerScope = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ShortcutController = ShortcutControllerSignalList
type ShortcutControllerSignalList = ('[ '("itemsChanged", Gio.ListModel.ListModelItemsChangedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

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

foreign import ccall "gtk_shortcut_controller_new" gtk_shortcut_controller_new :: 
    IO (Ptr ShortcutController)

-- | Creates a new shortcut controller.
shortcutControllerNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m ShortcutController
    -- ^ __Returns:__ a newly created shortcut controller
shortcutControllerNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
m ShortcutController
shortcutControllerNew  = IO ShortcutController -> m ShortcutController
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ShortcutController -> m ShortcutController)
-> IO ShortcutController -> m ShortcutController
forall a b. (a -> b) -> a -> b
$ do
    Ptr ShortcutController
result <- IO (Ptr ShortcutController)
gtk_shortcut_controller_new
    Text -> Ptr ShortcutController -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"shortcutControllerNew" Ptr ShortcutController
result
    ShortcutController
result' <- ((ManagedPtr ShortcutController -> ShortcutController)
-> Ptr ShortcutController -> IO ShortcutController
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr ShortcutController -> ShortcutController
ShortcutController) Ptr ShortcutController
result
    ShortcutController -> IO ShortcutController
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ShortcutController
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method ShortcutController::new_for_model
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "model"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ListModel" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GListModel` containing shortcuts"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gtk" , name = "ShortcutController" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_shortcut_controller_new_for_model" gtk_shortcut_controller_new_for_model :: 
    Ptr Gio.ListModel.ListModel ->          -- model : TInterface (Name {namespace = "Gio", name = "ListModel"})
    IO (Ptr ShortcutController)

-- | Creates a new shortcut controller that takes its shortcuts from
-- the given list model.
-- 
-- A controller created by this function does not let you add or
-- remove individual shortcuts using the shortcut controller api,
-- but you can change the contents of the model.
shortcutControllerNewForModel ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.ListModel.IsListModel a) =>
    a
    -- ^ /@model@/: a @GListModel@ containing shortcuts
    -> m ShortcutController
    -- ^ __Returns:__ a newly created shortcut controller
shortcutControllerNewForModel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsListModel a) =>
a -> m ShortcutController
shortcutControllerNewForModel a
model = IO ShortcutController -> m ShortcutController
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ShortcutController -> m ShortcutController)
-> IO ShortcutController -> m ShortcutController
forall a b. (a -> b) -> a -> b
$ do
    Ptr ListModel
model' <- a -> IO (Ptr ListModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
model
    Ptr ShortcutController
result <- Ptr ListModel -> IO (Ptr ShortcutController)
gtk_shortcut_controller_new_for_model Ptr ListModel
model'
    Text -> Ptr ShortcutController -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"shortcutControllerNewForModel" Ptr ShortcutController
result
    ShortcutController
result' <- ((ManagedPtr ShortcutController -> ShortcutController)
-> Ptr ShortcutController -> IO ShortcutController
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr ShortcutController -> ShortcutController
ShortcutController) Ptr ShortcutController
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
model
    ShortcutController -> IO ShortcutController
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ShortcutController
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method ShortcutController::add_shortcut
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ShortcutController" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the controller" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "shortcut"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Shortcut" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkShortcut`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_shortcut_controller_add_shortcut" gtk_shortcut_controller_add_shortcut :: 
    Ptr ShortcutController ->               -- self : TInterface (Name {namespace = "Gtk", name = "ShortcutController"})
    Ptr Gtk.Shortcut.Shortcut ->            -- shortcut : TInterface (Name {namespace = "Gtk", name = "Shortcut"})
    IO ()

-- | Adds /@shortcut@/ to the list of shortcuts handled by /@self@/.
-- 
-- If this controller uses an external shortcut list, this
-- function does nothing.
shortcutControllerAddShortcut ::
    (B.CallStack.HasCallStack, MonadIO m, IsShortcutController a, Gtk.Shortcut.IsShortcut b) =>
    a
    -- ^ /@self@/: the controller
    -> b
    -- ^ /@shortcut@/: a @GtkShortcut@
    -> m ()
shortcutControllerAddShortcut :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsShortcutController a, IsShortcut b) =>
a -> b -> m ()
shortcutControllerAddShortcut a
self b
shortcut = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr ShortcutController
self' <- a -> IO (Ptr ShortcutController)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Shortcut
shortcut' <- b -> IO (Ptr Shortcut)
forall a b. (HasCallStack, GObject a) => a -> IO (Ptr b)
B.ManagedPtr.disownObject b
shortcut
    Ptr ShortcutController -> Ptr Shortcut -> IO ()
gtk_shortcut_controller_add_shortcut Ptr ShortcutController
self' Ptr Shortcut
shortcut'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
shortcut
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ShortcutControllerAddShortcutMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsShortcutController a, Gtk.Shortcut.IsShortcut b) => O.OverloadedMethod ShortcutControllerAddShortcutMethodInfo a signature where
    overloadedMethod = shortcutControllerAddShortcut

instance O.OverloadedMethodInfo ShortcutControllerAddShortcutMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ShortcutController.shortcutControllerAddShortcut",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-ShortcutController.html#v:shortcutControllerAddShortcut"
        })


#endif

-- method ShortcutController::get_mnemonics_modifiers
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ShortcutController" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkShortcutController`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gdk" , name = "ModifierType" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_shortcut_controller_get_mnemonics_modifiers" gtk_shortcut_controller_get_mnemonics_modifiers :: 
    Ptr ShortcutController ->               -- self : TInterface (Name {namespace = "Gtk", name = "ShortcutController"})
    IO CUInt

-- | Gets the mnemonics modifiers for when this controller activates its shortcuts.
shortcutControllerGetMnemonicsModifiers ::
    (B.CallStack.HasCallStack, MonadIO m, IsShortcutController a) =>
    a
    -- ^ /@self@/: a @GtkShortcutController@
    -> m [Gdk.Flags.ModifierType]
    -- ^ __Returns:__ the controller\'s mnemonics modifiers
shortcutControllerGetMnemonicsModifiers :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsShortcutController a) =>
a -> m [ModifierType]
shortcutControllerGetMnemonicsModifiers a
self = IO [ModifierType] -> m [ModifierType]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [ModifierType] -> m [ModifierType])
-> IO [ModifierType] -> m [ModifierType]
forall a b. (a -> b) -> a -> b
$ do
    Ptr ShortcutController
self' <- a -> IO (Ptr ShortcutController)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CUInt
result <- Ptr ShortcutController -> IO CUInt
gtk_shortcut_controller_get_mnemonics_modifiers Ptr ShortcutController
self'
    let result' :: [ModifierType]
result' = CUInt -> [ModifierType]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    [ModifierType] -> IO [ModifierType]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [ModifierType]
result'

#if defined(ENABLE_OVERLOADING)
data ShortcutControllerGetMnemonicsModifiersMethodInfo
instance (signature ~ (m [Gdk.Flags.ModifierType]), MonadIO m, IsShortcutController a) => O.OverloadedMethod ShortcutControllerGetMnemonicsModifiersMethodInfo a signature where
    overloadedMethod = shortcutControllerGetMnemonicsModifiers

instance O.OverloadedMethodInfo ShortcutControllerGetMnemonicsModifiersMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ShortcutController.shortcutControllerGetMnemonicsModifiers",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-ShortcutController.html#v:shortcutControllerGetMnemonicsModifiers"
        })


#endif

-- method ShortcutController::get_scope
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ShortcutController" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkShortcutController`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "ShortcutScope" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_shortcut_controller_get_scope" gtk_shortcut_controller_get_scope :: 
    Ptr ShortcutController ->               -- self : TInterface (Name {namespace = "Gtk", name = "ShortcutController"})
    IO CUInt

-- | Gets the scope for when this controller activates its shortcuts.
-- 
-- See 'GI.Gtk.Objects.ShortcutController.shortcutControllerSetScope' for details.
shortcutControllerGetScope ::
    (B.CallStack.HasCallStack, MonadIO m, IsShortcutController a) =>
    a
    -- ^ /@self@/: a @GtkShortcutController@
    -> m Gtk.Enums.ShortcutScope
    -- ^ __Returns:__ the controller\'s scope
shortcutControllerGetScope :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsShortcutController a) =>
a -> m ShortcutScope
shortcutControllerGetScope a
self = IO ShortcutScope -> m ShortcutScope
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ShortcutScope -> m ShortcutScope)
-> IO ShortcutScope -> m ShortcutScope
forall a b. (a -> b) -> a -> b
$ do
    Ptr ShortcutController
self' <- a -> IO (Ptr ShortcutController)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CUInt
result <- Ptr ShortcutController -> IO CUInt
gtk_shortcut_controller_get_scope Ptr ShortcutController
self'
    let result' :: ShortcutScope
result' = (Int -> ShortcutScope
forall a. Enum a => Int -> a
toEnum (Int -> ShortcutScope) -> (CUInt -> Int) -> CUInt -> ShortcutScope
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    ShortcutScope -> IO ShortcutScope
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ShortcutScope
result'

#if defined(ENABLE_OVERLOADING)
data ShortcutControllerGetScopeMethodInfo
instance (signature ~ (m Gtk.Enums.ShortcutScope), MonadIO m, IsShortcutController a) => O.OverloadedMethod ShortcutControllerGetScopeMethodInfo a signature where
    overloadedMethod = shortcutControllerGetScope

instance O.OverloadedMethodInfo ShortcutControllerGetScopeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ShortcutController.shortcutControllerGetScope",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-ShortcutController.html#v:shortcutControllerGetScope"
        })


#endif

-- method ShortcutController::remove_shortcut
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ShortcutController" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the controller" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "shortcut"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Shortcut" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkShortcut`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_shortcut_controller_remove_shortcut" gtk_shortcut_controller_remove_shortcut :: 
    Ptr ShortcutController ->               -- self : TInterface (Name {namespace = "Gtk", name = "ShortcutController"})
    Ptr Gtk.Shortcut.Shortcut ->            -- shortcut : TInterface (Name {namespace = "Gtk", name = "Shortcut"})
    IO ()

-- | Removes /@shortcut@/ from the list of shortcuts handled by /@self@/.
-- 
-- If /@shortcut@/ had not been added to /@controller@/ or this controller
-- uses an external shortcut list, this function does nothing.
shortcutControllerRemoveShortcut ::
    (B.CallStack.HasCallStack, MonadIO m, IsShortcutController a, Gtk.Shortcut.IsShortcut b) =>
    a
    -- ^ /@self@/: the controller
    -> b
    -- ^ /@shortcut@/: a @GtkShortcut@
    -> m ()
shortcutControllerRemoveShortcut :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsShortcutController a, IsShortcut b) =>
a -> b -> m ()
shortcutControllerRemoveShortcut a
self b
shortcut = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr ShortcutController
self' <- a -> IO (Ptr ShortcutController)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Shortcut
shortcut' <- b -> IO (Ptr Shortcut)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
shortcut
    Ptr ShortcutController -> Ptr Shortcut -> IO ()
gtk_shortcut_controller_remove_shortcut Ptr ShortcutController
self' Ptr Shortcut
shortcut'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
shortcut
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ShortcutControllerRemoveShortcutMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsShortcutController a, Gtk.Shortcut.IsShortcut b) => O.OverloadedMethod ShortcutControllerRemoveShortcutMethodInfo a signature where
    overloadedMethod = shortcutControllerRemoveShortcut

instance O.OverloadedMethodInfo ShortcutControllerRemoveShortcutMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ShortcutController.shortcutControllerRemoveShortcut",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-ShortcutController.html#v:shortcutControllerRemoveShortcut"
        })


#endif

-- method ShortcutController::set_mnemonics_modifiers
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ShortcutController" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkShortcutController`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "modifiers"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "ModifierType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new mnemonics_modifiers to use"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_shortcut_controller_set_mnemonics_modifiers" gtk_shortcut_controller_set_mnemonics_modifiers :: 
    Ptr ShortcutController ->               -- self : TInterface (Name {namespace = "Gtk", name = "ShortcutController"})
    CUInt ->                                -- modifiers : TInterface (Name {namespace = "Gdk", name = "ModifierType"})
    IO ()

-- | Sets the controller to use the given modifier for mnemonics.
-- 
-- The mnemonics modifiers determines which modifiers need to be pressed to allow
-- activation of shortcuts with mnemonics triggers.
-- 
-- GTK normally uses the Alt modifier for mnemonics, except in @GtkPopoverMenu@s,
-- where mnemonics can be triggered without any modifiers. It should be very
-- rarely necessary to change this, and doing so is likely to interfere with
-- other shortcuts.
-- 
-- This value is only relevant for local shortcut controllers. Global and managed
-- shortcut controllers will have their shortcuts activated from other places which
-- have their own modifiers for activating mnemonics.
shortcutControllerSetMnemonicsModifiers ::
    (B.CallStack.HasCallStack, MonadIO m, IsShortcutController a) =>
    a
    -- ^ /@self@/: a @GtkShortcutController@
    -> [Gdk.Flags.ModifierType]
    -- ^ /@modifiers@/: the new mnemonics_modifiers to use
    -> m ()
shortcutControllerSetMnemonicsModifiers :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsShortcutController a) =>
a -> [ModifierType] -> m ()
shortcutControllerSetMnemonicsModifiers a
self [ModifierType]
modifiers = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr ShortcutController
self' <- a -> IO (Ptr ShortcutController)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let modifiers' :: CUInt
modifiers' = [ModifierType] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ModifierType]
modifiers
    Ptr ShortcutController -> CUInt -> IO ()
gtk_shortcut_controller_set_mnemonics_modifiers Ptr ShortcutController
self' CUInt
modifiers'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ShortcutControllerSetMnemonicsModifiersMethodInfo
instance (signature ~ ([Gdk.Flags.ModifierType] -> m ()), MonadIO m, IsShortcutController a) => O.OverloadedMethod ShortcutControllerSetMnemonicsModifiersMethodInfo a signature where
    overloadedMethod = shortcutControllerSetMnemonicsModifiers

instance O.OverloadedMethodInfo ShortcutControllerSetMnemonicsModifiersMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ShortcutController.shortcutControllerSetMnemonicsModifiers",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-ShortcutController.html#v:shortcutControllerSetMnemonicsModifiers"
        })


#endif

-- method ShortcutController::set_scope
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ShortcutController" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkShortcutController`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "scope"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ShortcutScope" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new scope to use"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_shortcut_controller_set_scope" gtk_shortcut_controller_set_scope :: 
    Ptr ShortcutController ->               -- self : TInterface (Name {namespace = "Gtk", name = "ShortcutController"})
    CUInt ->                                -- scope : TInterface (Name {namespace = "Gtk", name = "ShortcutScope"})
    IO ()

-- | Sets the controller to have the given /@scope@/.
-- 
-- The scope allows shortcuts to be activated outside of the normal
-- event propagation. In particular, it allows installing global
-- keyboard shortcuts that can be activated even when a widget does
-- not have focus.
-- 
-- With 'GI.Gtk.Enums.ShortcutScopeLocal', shortcuts will only be activated
-- when the widget has focus.
shortcutControllerSetScope ::
    (B.CallStack.HasCallStack, MonadIO m, IsShortcutController a) =>
    a
    -- ^ /@self@/: a @GtkShortcutController@
    -> Gtk.Enums.ShortcutScope
    -- ^ /@scope@/: the new scope to use
    -> m ()
shortcutControllerSetScope :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsShortcutController a) =>
a -> ShortcutScope -> m ()
shortcutControllerSetScope a
self ShortcutScope
scope = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr ShortcutController
self' <- a -> IO (Ptr ShortcutController)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let scope' :: CUInt
scope' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (ShortcutScope -> Int) -> ShortcutScope -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortcutScope -> Int
forall a. Enum a => a -> Int
fromEnum) ShortcutScope
scope
    Ptr ShortcutController -> CUInt -> IO ()
gtk_shortcut_controller_set_scope Ptr ShortcutController
self' CUInt
scope'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ShortcutControllerSetScopeMethodInfo
instance (signature ~ (Gtk.Enums.ShortcutScope -> m ()), MonadIO m, IsShortcutController a) => O.OverloadedMethod ShortcutControllerSetScopeMethodInfo a signature where
    overloadedMethod = shortcutControllerSetScope

instance O.OverloadedMethodInfo ShortcutControllerSetScopeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ShortcutController.shortcutControllerSetScope",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-ShortcutController.html#v:shortcutControllerSetScope"
        })


#endif