{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GtkShortcutTrigger@ tracks how a @GtkShortcut@ should be activated.
-- 
-- To find out if a @GtkShortcutTrigger@ triggers, you can call
-- 'GI.Gtk.Objects.ShortcutTrigger.shortcutTriggerTrigger' on a @GdkEvent@.
-- 
-- @GtkShortcutTriggers@ contain functions that allow easy presentation
-- to end users as well as being printed for debugging.
-- 
-- All @GtkShortcutTriggers@ are immutable, you can only specify their
-- properties during construction. If you want to change a trigger, you
-- have to replace it with a new one.

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

module GI.Gtk.Objects.ShortcutTrigger
    ( 

-- * Exported types
    ShortcutTrigger(..)                     ,
    IsShortcutTrigger                       ,
    toShortcutTrigger                       ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [compare]("GI.Gtk.Objects.ShortcutTrigger#g:method:compare"), [equal]("GI.Gtk.Objects.ShortcutTrigger#g:method:equal"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [hash]("GI.Gtk.Objects.ShortcutTrigger#g:method:hash"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [print]("GI.Gtk.Objects.ShortcutTrigger#g:method:print"), [printLabel]("GI.Gtk.Objects.ShortcutTrigger#g:method:printLabel"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [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"), [toLabel]("GI.Gtk.Objects.ShortcutTrigger#g:method:toLabel"), [toString]("GI.Gtk.Objects.ShortcutTrigger#g:method:toString"), [trigger]("GI.Gtk.Objects.ShortcutTrigger#g:method:trigger"), [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)
    ResolveShortcutTriggerMethod            ,
#endif

-- ** compare #method:compare#

#if defined(ENABLE_OVERLOADING)
    ShortcutTriggerCompareMethodInfo        ,
#endif
    shortcutTriggerCompare                  ,


-- ** equal #method:equal#

#if defined(ENABLE_OVERLOADING)
    ShortcutTriggerEqualMethodInfo          ,
#endif
    shortcutTriggerEqual                    ,


-- ** hash #method:hash#

#if defined(ENABLE_OVERLOADING)
    ShortcutTriggerHashMethodInfo           ,
#endif
    shortcutTriggerHash                     ,


-- ** parseString #method:parseString#

    shortcutTriggerParseString              ,


-- ** print #method:print#

#if defined(ENABLE_OVERLOADING)
    ShortcutTriggerPrintMethodInfo          ,
#endif
    shortcutTriggerPrint                    ,


-- ** printLabel #method:printLabel#

#if defined(ENABLE_OVERLOADING)
    ShortcutTriggerPrintLabelMethodInfo     ,
#endif
    shortcutTriggerPrintLabel               ,


-- ** toLabel #method:toLabel#

#if defined(ENABLE_OVERLOADING)
    ShortcutTriggerToLabelMethodInfo        ,
#endif
    shortcutTriggerToLabel                  ,


-- ** toString #method:toString#

#if defined(ENABLE_OVERLOADING)
    ShortcutTriggerToStringMethodInfo       ,
#endif
    shortcutTriggerToString                 ,


-- ** trigger #method:trigger#

#if defined(ENABLE_OVERLOADING)
    ShortcutTriggerTriggerMethodInfo        ,
#endif
    shortcutTriggerTrigger                  ,




    ) 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.Kind as DK
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.GLib.Structs.String as GLib.String
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Enums as Gdk.Enums
import qualified GI.Gdk.Objects.Display as Gdk.Display
import qualified GI.Gdk.Objects.Event as Gdk.Event

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

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

foreign import ccall "gtk_shortcut_trigger_get_type"
    c_gtk_shortcut_trigger_get_type :: IO B.Types.GType

instance B.Types.TypedObject ShortcutTrigger where
    glibType :: IO GType
glibType = IO GType
c_gtk_shortcut_trigger_get_type

instance B.Types.GObject ShortcutTrigger

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveShortcutTriggerMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveShortcutTriggerMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveShortcutTriggerMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveShortcutTriggerMethod "compare" o = ShortcutTriggerCompareMethodInfo
    ResolveShortcutTriggerMethod "equal" o = ShortcutTriggerEqualMethodInfo
    ResolveShortcutTriggerMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveShortcutTriggerMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveShortcutTriggerMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveShortcutTriggerMethod "hash" o = ShortcutTriggerHashMethodInfo
    ResolveShortcutTriggerMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveShortcutTriggerMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveShortcutTriggerMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveShortcutTriggerMethod "print" o = ShortcutTriggerPrintMethodInfo
    ResolveShortcutTriggerMethod "printLabel" o = ShortcutTriggerPrintLabelMethodInfo
    ResolveShortcutTriggerMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveShortcutTriggerMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveShortcutTriggerMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveShortcutTriggerMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveShortcutTriggerMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveShortcutTriggerMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveShortcutTriggerMethod "toLabel" o = ShortcutTriggerToLabelMethodInfo
    ResolveShortcutTriggerMethod "toString" o = ShortcutTriggerToStringMethodInfo
    ResolveShortcutTriggerMethod "trigger" o = ShortcutTriggerTriggerMethodInfo
    ResolveShortcutTriggerMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveShortcutTriggerMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveShortcutTriggerMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveShortcutTriggerMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveShortcutTriggerMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveShortcutTriggerMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveShortcutTriggerMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveShortcutTriggerMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveShortcutTriggerMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ShortcutTrigger
type instance O.AttributeList ShortcutTrigger = ShortcutTriggerAttributeList
type ShortcutTriggerAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ShortcutTrigger = ShortcutTriggerSignalList
type ShortcutTriggerSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method ShortcutTrigger::parse_string
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "string"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the string to parse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "ShortcutTrigger" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_shortcut_trigger_parse_string" gtk_shortcut_trigger_parse_string :: 
    CString ->                              -- string : TBasicType TUTF8
    IO (Ptr ShortcutTrigger)

-- | Tries to parse the given string into a trigger.
-- 
-- On success, the parsed trigger is returned.
-- When parsing failed, 'P.Nothing' is returned.
-- 
-- The accepted strings are:
-- 
--   - @never@, for @GtkNeverTrigger@
--   - a string parsed by 'GI.Gtk.Functions.acceleratorParse', for a @GtkKeyvalTrigger@, e.g. @\<Control>C@
--   - underscore, followed by a single character, for @GtkMnemonicTrigger@, e.g. @_l@
--   - two valid trigger strings, separated by a @|@ character, for a
--     @GtkAlternativeTrigger@: @\<Control>q|\<Control>w@
-- 
-- Note that you will have to escape the @\<@ and @>@ characters when specifying
-- triggers in XML files, such as GtkBuilder ui files. Use @&lt;@ instead of
-- @\<@ and @&gt;@ instead of @>@.
shortcutTriggerParseString ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@string@/: the string to parse
    -> m (Maybe ShortcutTrigger)
    -- ^ __Returns:__ a new @GtkShortcutTrigger@
shortcutTriggerParseString :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m (Maybe ShortcutTrigger)
shortcutTriggerParseString Text
string = IO (Maybe ShortcutTrigger) -> m (Maybe ShortcutTrigger)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ShortcutTrigger) -> m (Maybe ShortcutTrigger))
-> IO (Maybe ShortcutTrigger) -> m (Maybe ShortcutTrigger)
forall a b. (a -> b) -> a -> b
$ do
    CString
string' <- Text -> IO CString
textToCString Text
string
    Ptr ShortcutTrigger
result <- CString -> IO (Ptr ShortcutTrigger)
gtk_shortcut_trigger_parse_string CString
string'
    Maybe ShortcutTrigger
maybeResult <- Ptr ShortcutTrigger
-> (Ptr ShortcutTrigger -> IO ShortcutTrigger)
-> IO (Maybe ShortcutTrigger)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr ShortcutTrigger
result ((Ptr ShortcutTrigger -> IO ShortcutTrigger)
 -> IO (Maybe ShortcutTrigger))
-> (Ptr ShortcutTrigger -> IO ShortcutTrigger)
-> IO (Maybe ShortcutTrigger)
forall a b. (a -> b) -> a -> b
$ \Ptr ShortcutTrigger
result' -> do
        ShortcutTrigger
result'' <- ((ManagedPtr ShortcutTrigger -> ShortcutTrigger)
-> Ptr ShortcutTrigger -> IO ShortcutTrigger
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr ShortcutTrigger -> ShortcutTrigger
ShortcutTrigger) Ptr ShortcutTrigger
result'
        ShortcutTrigger -> IO ShortcutTrigger
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ShortcutTrigger
result''
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
string'
    Maybe ShortcutTrigger -> IO (Maybe ShortcutTrigger)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ShortcutTrigger
maybeResult

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "gtk_shortcut_trigger_compare" gtk_shortcut_trigger_compare :: 
    Ptr ShortcutTrigger ->                  -- trigger1 : TInterface (Name {namespace = "Gtk", name = "ShortcutTrigger"})
    Ptr ShortcutTrigger ->                  -- trigger2 : TInterface (Name {namespace = "Gtk", name = "ShortcutTrigger"})
    IO Int32

-- | The types of /@trigger1@/ and /@trigger2@/ are @gconstpointer@ only to allow
-- use of this function as a @GCompareFunc@.
-- 
-- They must each be a @GtkShortcutTrigger@.
shortcutTriggerCompare ::
    (B.CallStack.HasCallStack, MonadIO m, IsShortcutTrigger a, IsShortcutTrigger b) =>
    a
    -- ^ /@trigger1@/: a @GtkShortcutTrigger@
    -> b
    -- ^ /@trigger2@/: a @GtkShortcutTrigger@
    -> m Int32
    -- ^ __Returns:__ An integer less than, equal to, or greater than zero if
    --   /@trigger1@/ is found, respectively, to be less than, to match,
    --   or be greater than /@trigger2@/.
shortcutTriggerCompare :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsShortcutTrigger a,
 IsShortcutTrigger b) =>
a -> b -> m Int32
shortcutTriggerCompare a
trigger1 b
trigger2 = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr ShortcutTrigger
trigger1' <- a -> IO (Ptr ShortcutTrigger)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
trigger1
    Ptr ShortcutTrigger
trigger2' <- b -> IO (Ptr ShortcutTrigger)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
trigger2
    Int32
result <- Ptr ShortcutTrigger -> Ptr ShortcutTrigger -> IO Int32
gtk_shortcut_trigger_compare Ptr ShortcutTrigger
trigger1' Ptr ShortcutTrigger
trigger2'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
trigger1
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
trigger2
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data ShortcutTriggerCompareMethodInfo
instance (signature ~ (b -> m Int32), MonadIO m, IsShortcutTrigger a, IsShortcutTrigger b) => O.OverloadedMethod ShortcutTriggerCompareMethodInfo a signature where
    overloadedMethod = shortcutTriggerCompare

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


#endif

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

foreign import ccall "gtk_shortcut_trigger_equal" gtk_shortcut_trigger_equal :: 
    Ptr ShortcutTrigger ->                  -- trigger1 : TInterface (Name {namespace = "Gtk", name = "ShortcutTrigger"})
    Ptr ShortcutTrigger ->                  -- trigger2 : TInterface (Name {namespace = "Gtk", name = "ShortcutTrigger"})
    IO CInt

-- | Checks if /@trigger1@/ and /@trigger2@/ trigger under the same conditions.
-- 
-- The types of /@one@/ and /@two@/ are @gconstpointer@ only to allow use of this
-- function with @GHashTable@. They must each be a @GtkShortcutTrigger@.
shortcutTriggerEqual ::
    (B.CallStack.HasCallStack, MonadIO m, IsShortcutTrigger a, IsShortcutTrigger b) =>
    a
    -- ^ /@trigger1@/: a @GtkShortcutTrigger@
    -> b
    -- ^ /@trigger2@/: a @GtkShortcutTrigger@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@trigger1@/ and /@trigger2@/ are equal
shortcutTriggerEqual :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsShortcutTrigger a,
 IsShortcutTrigger b) =>
a -> b -> m Bool
shortcutTriggerEqual a
trigger1 b
trigger2 = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr ShortcutTrigger
trigger1' <- a -> IO (Ptr ShortcutTrigger)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
trigger1
    Ptr ShortcutTrigger
trigger2' <- b -> IO (Ptr ShortcutTrigger)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
trigger2
    CInt
result <- Ptr ShortcutTrigger -> Ptr ShortcutTrigger -> IO CInt
gtk_shortcut_trigger_equal Ptr ShortcutTrigger
trigger1' Ptr ShortcutTrigger
trigger2'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
trigger1
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
trigger2
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ShortcutTriggerEqualMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsShortcutTrigger a, IsShortcutTrigger b) => O.OverloadedMethod ShortcutTriggerEqualMethodInfo a signature where
    overloadedMethod = shortcutTriggerEqual

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


#endif

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

foreign import ccall "gtk_shortcut_trigger_hash" gtk_shortcut_trigger_hash :: 
    Ptr ShortcutTrigger ->                  -- trigger : TInterface (Name {namespace = "Gtk", name = "ShortcutTrigger"})
    IO Word32

-- | Generates a hash value for a @GtkShortcutTrigger@.
-- 
-- The output of this function is guaranteed to be the same for a given
-- value only per-process. It may change between different processor
-- architectures or even different versions of GTK. Do not use this
-- function as a basis for building protocols or file formats.
-- 
-- The types of /@trigger@/ is @gconstpointer@ only to allow use of this
-- function with @GHashTable@. They must each be a @GtkShortcutTrigger@.
shortcutTriggerHash ::
    (B.CallStack.HasCallStack, MonadIO m, IsShortcutTrigger a) =>
    a
    -- ^ /@trigger@/: a @GtkShortcutTrigger@
    -> m Word32
    -- ^ __Returns:__ a hash value corresponding to /@trigger@/
shortcutTriggerHash :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsShortcutTrigger a) =>
a -> m Word32
shortcutTriggerHash a
trigger = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr ShortcutTrigger
trigger' <- a -> IO (Ptr ShortcutTrigger)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
trigger
    Word32
result <- Ptr ShortcutTrigger -> IO Word32
gtk_shortcut_trigger_hash Ptr ShortcutTrigger
trigger'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
trigger
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data ShortcutTriggerHashMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsShortcutTrigger a) => O.OverloadedMethod ShortcutTriggerHashMethodInfo a signature where
    overloadedMethod = shortcutTriggerHash

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


#endif

-- method ShortcutTrigger::print
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ShortcutTrigger" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkShortcutTrigger`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "string"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GString` to print into"
--                 , 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_trigger_print" gtk_shortcut_trigger_print :: 
    Ptr ShortcutTrigger ->                  -- self : TInterface (Name {namespace = "Gtk", name = "ShortcutTrigger"})
    Ptr GLib.String.String ->               -- string : TInterface (Name {namespace = "GLib", name = "String"})
    IO ()

-- | Prints the given trigger into a string for the developer.
-- This is meant for debugging and logging.
-- 
-- The form of the representation may change at any time
-- and is not guaranteed to stay identical.
shortcutTriggerPrint ::
    (B.CallStack.HasCallStack, MonadIO m, IsShortcutTrigger a) =>
    a
    -- ^ /@self@/: a @GtkShortcutTrigger@
    -> GLib.String.String
    -- ^ /@string@/: a @GString@ to print into
    -> m ()
shortcutTriggerPrint :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsShortcutTrigger a) =>
a -> String -> m ()
shortcutTriggerPrint a
self String
string = 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 ShortcutTrigger
self' <- a -> IO (Ptr ShortcutTrigger)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    Ptr ShortcutTrigger -> Ptr String -> IO ()
gtk_shortcut_trigger_print Ptr ShortcutTrigger
self' Ptr String
string'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ShortcutTriggerPrintMethodInfo
instance (signature ~ (GLib.String.String -> m ()), MonadIO m, IsShortcutTrigger a) => O.OverloadedMethod ShortcutTriggerPrintMethodInfo a signature where
    overloadedMethod = shortcutTriggerPrint

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


#endif

-- method ShortcutTrigger::print_label
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ShortcutTrigger" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkShortcutTrigger`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "display"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Display" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "`GdkDisplay` to print for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "string"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GString` to print into"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_shortcut_trigger_print_label" gtk_shortcut_trigger_print_label :: 
    Ptr ShortcutTrigger ->                  -- self : TInterface (Name {namespace = "Gtk", name = "ShortcutTrigger"})
    Ptr Gdk.Display.Display ->              -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    Ptr GLib.String.String ->               -- string : TInterface (Name {namespace = "GLib", name = "String"})
    IO CInt

-- | Prints the given trigger into a string.
-- 
-- This function is returning a translated string for presentation
-- to end users for example in menu items or in help texts.
-- 
-- The /@display@/ in use may influence the resulting string in
-- various forms, such as resolving hardware keycodes or by
-- causing display-specific modifier names.
-- 
-- The form of the representation may change at any time and is
-- not guaranteed to stay identical.
shortcutTriggerPrintLabel ::
    (B.CallStack.HasCallStack, MonadIO m, IsShortcutTrigger a, Gdk.Display.IsDisplay b) =>
    a
    -- ^ /@self@/: a @GtkShortcutTrigger@
    -> b
    -- ^ /@display@/: @GdkDisplay@ to print for
    -> GLib.String.String
    -- ^ /@string@/: a @GString@ to print into
    -> m Bool
    -- ^ __Returns:__ 'P.True' if something was printed or 'P.False' if the
    --   trigger did not have a textual representation suitable
    --   for end users.
shortcutTriggerPrintLabel :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsShortcutTrigger a, IsDisplay b) =>
a -> b -> String -> m Bool
shortcutTriggerPrintLabel a
self b
display String
string = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr ShortcutTrigger
self' <- a -> IO (Ptr ShortcutTrigger)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Display
display' <- b -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
display
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    CInt
result <- Ptr ShortcutTrigger -> Ptr Display -> Ptr String -> IO CInt
gtk_shortcut_trigger_print_label Ptr ShortcutTrigger
self' Ptr Display
display' Ptr String
string'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
display
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ShortcutTriggerPrintLabelMethodInfo
instance (signature ~ (b -> GLib.String.String -> m Bool), MonadIO m, IsShortcutTrigger a, Gdk.Display.IsDisplay b) => O.OverloadedMethod ShortcutTriggerPrintLabelMethodInfo a signature where
    overloadedMethod = shortcutTriggerPrintLabel

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


#endif

-- method ShortcutTrigger::to_label
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ShortcutTrigger" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkShortcutTrigger`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "display"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Display" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "`GdkDisplay` to print for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_shortcut_trigger_to_label" gtk_shortcut_trigger_to_label :: 
    Ptr ShortcutTrigger ->                  -- self : TInterface (Name {namespace = "Gtk", name = "ShortcutTrigger"})
    Ptr Gdk.Display.Display ->              -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO CString

-- | Gets textual representation for the given trigger.
-- 
-- This function is returning a translated string for
-- presentation to end users for example in menu items
-- or in help texts.
-- 
-- The /@display@/ in use may influence the resulting string in
-- various forms, such as resolving hardware keycodes or by
-- causing display-specific modifier names.
-- 
-- The form of the representation may change at any time and is
-- not guaranteed to stay identical.
shortcutTriggerToLabel ::
    (B.CallStack.HasCallStack, MonadIO m, IsShortcutTrigger a, Gdk.Display.IsDisplay b) =>
    a
    -- ^ /@self@/: a @GtkShortcutTrigger@
    -> b
    -- ^ /@display@/: @GdkDisplay@ to print for
    -> m T.Text
    -- ^ __Returns:__ a new string
shortcutTriggerToLabel :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsShortcutTrigger a, IsDisplay b) =>
a -> b -> m Text
shortcutTriggerToLabel a
self b
display = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr ShortcutTrigger
self' <- a -> IO (Ptr ShortcutTrigger)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Display
display' <- b -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
display
    CString
result <- Ptr ShortcutTrigger -> Ptr Display -> IO CString
gtk_shortcut_trigger_to_label Ptr ShortcutTrigger
self' Ptr Display
display'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"shortcutTriggerToLabel" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
display
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ShortcutTriggerToLabelMethodInfo
instance (signature ~ (b -> m T.Text), MonadIO m, IsShortcutTrigger a, Gdk.Display.IsDisplay b) => O.OverloadedMethod ShortcutTriggerToLabelMethodInfo a signature where
    overloadedMethod = shortcutTriggerToLabel

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


#endif

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

foreign import ccall "gtk_shortcut_trigger_to_string" gtk_shortcut_trigger_to_string :: 
    Ptr ShortcutTrigger ->                  -- self : TInterface (Name {namespace = "Gtk", name = "ShortcutTrigger"})
    IO CString

-- | Prints the given trigger into a human-readable string.
-- 
-- This is a small wrapper around 'GI.Gtk.Objects.ShortcutTrigger.shortcutTriggerPrint'
-- to help when debugging.
shortcutTriggerToString ::
    (B.CallStack.HasCallStack, MonadIO m, IsShortcutTrigger a) =>
    a
    -- ^ /@self@/: a @GtkShortcutTrigger@
    -> m T.Text
    -- ^ __Returns:__ a new string
shortcutTriggerToString :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsShortcutTrigger a) =>
a -> m Text
shortcutTriggerToString a
self = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr ShortcutTrigger
self' <- a -> IO (Ptr ShortcutTrigger)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr ShortcutTrigger -> IO CString
gtk_shortcut_trigger_to_string Ptr ShortcutTrigger
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"shortcutTriggerToString" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ShortcutTriggerToStringMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsShortcutTrigger a) => O.OverloadedMethod ShortcutTriggerToStringMethodInfo a signature where
    overloadedMethod = shortcutTriggerToString

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


#endif

-- method ShortcutTrigger::trigger
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ShortcutTrigger" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkShortcutTrigger`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "event"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Event" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the event to check" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "enable_mnemonics"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "%TRUE if mnemonics should trigger. Usually the\n  value of this property is determined by checking that the passed\n  in @event is a Key event and has the right modifiers set."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "KeyMatch" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_shortcut_trigger_trigger" gtk_shortcut_trigger_trigger :: 
    Ptr ShortcutTrigger ->                  -- self : TInterface (Name {namespace = "Gtk", name = "ShortcutTrigger"})
    Ptr Gdk.Event.Event ->                  -- event : TInterface (Name {namespace = "Gdk", name = "Event"})
    CInt ->                                 -- enable_mnemonics : TBasicType TBoolean
    IO CUInt

-- | Checks if the given /@event@/ triggers /@self@/.
shortcutTriggerTrigger ::
    (B.CallStack.HasCallStack, MonadIO m, IsShortcutTrigger a, Gdk.Event.IsEvent b) =>
    a
    -- ^ /@self@/: a @GtkShortcutTrigger@
    -> b
    -- ^ /@event@/: the event to check
    -> Bool
    -- ^ /@enableMnemonics@/: 'P.True' if mnemonics should trigger. Usually the
    --   value of this property is determined by checking that the passed
    --   in /@event@/ is a Key event and has the right modifiers set.
    -> m Gdk.Enums.KeyMatch
    -- ^ __Returns:__ Whether the event triggered the shortcut
shortcutTriggerTrigger :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsShortcutTrigger a, IsEvent b) =>
a -> b -> Bool -> m KeyMatch
shortcutTriggerTrigger a
self b
event Bool
enableMnemonics = IO KeyMatch -> m KeyMatch
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO KeyMatch -> m KeyMatch) -> IO KeyMatch -> m KeyMatch
forall a b. (a -> b) -> a -> b
$ do
    Ptr ShortcutTrigger
self' <- a -> IO (Ptr ShortcutTrigger)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Event
event' <- b -> IO (Ptr Event)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
event
    let enableMnemonics' :: CInt
enableMnemonics' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
enableMnemonics
    CUInt
result <- Ptr ShortcutTrigger -> Ptr Event -> CInt -> IO CUInt
gtk_shortcut_trigger_trigger Ptr ShortcutTrigger
self' Ptr Event
event' CInt
enableMnemonics'
    let result' :: KeyMatch
result' = (Int -> KeyMatch
forall a. Enum a => Int -> a
toEnum (Int -> KeyMatch) -> (CUInt -> Int) -> CUInt -> KeyMatch
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
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
event
    KeyMatch -> IO KeyMatch
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return KeyMatch
result'

#if defined(ENABLE_OVERLOADING)
data ShortcutTriggerTriggerMethodInfo
instance (signature ~ (b -> Bool -> m Gdk.Enums.KeyMatch), MonadIO m, IsShortcutTrigger a, Gdk.Event.IsEvent b) => O.OverloadedMethod ShortcutTriggerTriggerMethodInfo a signature where
    overloadedMethod = shortcutTriggerTrigger

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


#endif