{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.ShortcutTrigger
(
ShortcutTrigger(..) ,
IsShortcutTrigger ,
toShortcutTrigger ,
#if defined(ENABLE_OVERLOADING)
ResolveShortcutTriggerMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ShortcutTriggerCompareMethodInfo ,
#endif
shortcutTriggerCompare ,
#if defined(ENABLE_OVERLOADING)
ShortcutTriggerEqualMethodInfo ,
#endif
shortcutTriggerEqual ,
#if defined(ENABLE_OVERLOADING)
ShortcutTriggerHashMethodInfo ,
#endif
shortcutTriggerHash ,
shortcutTriggerParseString ,
#if defined(ENABLE_OVERLOADING)
ShortcutTriggerPrintMethodInfo ,
#endif
shortcutTriggerPrint ,
#if defined(ENABLE_OVERLOADING)
ShortcutTriggerPrintLabelMethodInfo ,
#endif
shortcutTriggerPrintLabel ,
#if defined(ENABLE_OVERLOADING)
ShortcutTriggerToLabelMethodInfo ,
#endif
shortcutTriggerToLabel ,
#if defined(ENABLE_OVERLOADING)
ShortcutTriggerToStringMethodInfo ,
#endif
shortcutTriggerToString ,
#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 Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
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
#else
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
#endif
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
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]
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
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 <- 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 /= FP.nullPtr
then P.Just <$> B.ManagedPtr.newObject ShortcutTrigger ptr
else return 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
foreign import ccall "gtk_shortcut_trigger_parse_string" gtk_shortcut_trigger_parse_string ::
CString ->
IO (Ptr ShortcutTrigger)
shortcutTriggerParseString ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> m (Maybe ShortcutTrigger)
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
string' <- Text -> IO CString
textToCString Text
string
result <- gtk_shortcut_trigger_parse_string string'
maybeResult <- convertIfNonNull result $ \Ptr ShortcutTrigger
result' -> do
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'
return result''
freeMem string'
return maybeResult
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_shortcut_trigger_compare" gtk_shortcut_trigger_compare ::
Ptr ShortcutTrigger ->
Ptr ShortcutTrigger ->
IO Int32
shortcutTriggerCompare ::
(B.CallStack.HasCallStack, MonadIO m, IsShortcutTrigger a, IsShortcutTrigger b) =>
a
-> b
-> m Int32
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
trigger1' <- a -> IO (Ptr ShortcutTrigger)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
trigger1
trigger2' <- unsafeManagedPtrCastPtr trigger2
result <- gtk_shortcut_trigger_compare trigger1' trigger2'
touchManagedPtr trigger1
touchManagedPtr trigger2
return 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-gtk4-4.0.12/docs/GI-Gtk-Objects-ShortcutTrigger.html#v:shortcutTriggerCompare"
})
#endif
foreign import ccall "gtk_shortcut_trigger_equal" gtk_shortcut_trigger_equal ::
Ptr ShortcutTrigger ->
Ptr ShortcutTrigger ->
IO CInt
shortcutTriggerEqual ::
(B.CallStack.HasCallStack, MonadIO m, IsShortcutTrigger a, IsShortcutTrigger b) =>
a
-> b
-> m Bool
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
trigger1' <- a -> IO (Ptr ShortcutTrigger)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
trigger1
trigger2' <- unsafeManagedPtrCastPtr trigger2
result <- gtk_shortcut_trigger_equal trigger1' trigger2'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr trigger1
touchManagedPtr trigger2
return 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-gtk4-4.0.12/docs/GI-Gtk-Objects-ShortcutTrigger.html#v:shortcutTriggerEqual"
})
#endif
foreign import ccall "gtk_shortcut_trigger_hash" gtk_shortcut_trigger_hash ::
Ptr ShortcutTrigger ->
IO Word32
shortcutTriggerHash ::
(B.CallStack.HasCallStack, MonadIO m, IsShortcutTrigger a) =>
a
-> m Word32
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
trigger' <- a -> IO (Ptr ShortcutTrigger)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
trigger
result <- gtk_shortcut_trigger_hash trigger'
touchManagedPtr trigger
return 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-gtk4-4.0.12/docs/GI-Gtk-Objects-ShortcutTrigger.html#v:shortcutTriggerHash"
})
#endif
foreign import ccall "gtk_shortcut_trigger_print" gtk_shortcut_trigger_print ::
Ptr ShortcutTrigger ->
Ptr GLib.String.String ->
IO ()
shortcutTriggerPrint ::
(B.CallStack.HasCallStack, MonadIO m, IsShortcutTrigger a) =>
a
-> GLib.String.String
-> 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
self' <- a -> IO (Ptr ShortcutTrigger)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
string' <- unsafeManagedPtrGetPtr string
gtk_shortcut_trigger_print self' string'
touchManagedPtr self
touchManagedPtr string
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-gtk4-4.0.12/docs/GI-Gtk-Objects-ShortcutTrigger.html#v:shortcutTriggerPrint"
})
#endif
foreign import ccall "gtk_shortcut_trigger_print_label" gtk_shortcut_trigger_print_label ::
Ptr ShortcutTrigger ->
Ptr Gdk.Display.Display ->
Ptr GLib.String.String ->
IO CInt
shortcutTriggerPrintLabel ::
(B.CallStack.HasCallStack, MonadIO m, IsShortcutTrigger a, Gdk.Display.IsDisplay b) =>
a
-> b
-> GLib.String.String
-> m Bool
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
self' <- a -> IO (Ptr ShortcutTrigger)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
display' <- unsafeManagedPtrCastPtr display
string' <- unsafeManagedPtrGetPtr string
result <- gtk_shortcut_trigger_print_label self' display' string'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr self
touchManagedPtr display
touchManagedPtr string
return 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-gtk4-4.0.12/docs/GI-Gtk-Objects-ShortcutTrigger.html#v:shortcutTriggerPrintLabel"
})
#endif
foreign import ccall "gtk_shortcut_trigger_to_label" gtk_shortcut_trigger_to_label ::
Ptr ShortcutTrigger ->
Ptr Gdk.Display.Display ->
IO CString
shortcutTriggerToLabel ::
(B.CallStack.HasCallStack, MonadIO m, IsShortcutTrigger a, Gdk.Display.IsDisplay b) =>
a
-> b
-> m T.Text
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
self' <- a -> IO (Ptr ShortcutTrigger)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
display' <- unsafeManagedPtrCastPtr display
result <- gtk_shortcut_trigger_to_label self' display'
checkUnexpectedReturnNULL "shortcutTriggerToLabel" result
result' <- cstringToText result
freeMem result
touchManagedPtr self
touchManagedPtr display
return 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-gtk4-4.0.12/docs/GI-Gtk-Objects-ShortcutTrigger.html#v:shortcutTriggerToLabel"
})
#endif
foreign import ccall "gtk_shortcut_trigger_to_string" gtk_shortcut_trigger_to_string ::
Ptr ShortcutTrigger ->
IO CString
shortcutTriggerToString ::
(B.CallStack.HasCallStack, MonadIO m, IsShortcutTrigger a) =>
a
-> m T.Text
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
self' <- a -> IO (Ptr ShortcutTrigger)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
result <- gtk_shortcut_trigger_to_string self'
checkUnexpectedReturnNULL "shortcutTriggerToString" result
result' <- cstringToText result
freeMem result
touchManagedPtr self
return 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-gtk4-4.0.12/docs/GI-Gtk-Objects-ShortcutTrigger.html#v:shortcutTriggerToString"
})
#endif
foreign import ccall "gtk_shortcut_trigger_trigger" gtk_shortcut_trigger_trigger ::
Ptr ShortcutTrigger ->
Ptr Gdk.Event.Event ->
CInt ->
IO CUInt
shortcutTriggerTrigger ::
(B.CallStack.HasCallStack, MonadIO m, IsShortcutTrigger a, Gdk.Event.IsEvent b) =>
a
-> b
-> Bool
-> m Gdk.Enums.KeyMatch
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
self' <- a -> IO (Ptr ShortcutTrigger)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
event' <- unsafeManagedPtrCastPtr event
let 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
result <- gtk_shortcut_trigger_trigger self' event' enableMnemonics'
let 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
touchManagedPtr self
touchManagedPtr event
return 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-gtk4-4.0.12/docs/GI-Gtk-Objects-ShortcutTrigger.html#v:shortcutTriggerTrigger"
})
#endif