{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.ShortcutController
(
ShortcutController(..) ,
IsShortcutController ,
toShortcutController ,
#if defined(ENABLE_OVERLOADING)
ResolveShortcutControllerMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ShortcutControllerAddShortcutMethodInfo ,
#endif
shortcutControllerAddShortcut ,
#if defined(ENABLE_OVERLOADING)
ShortcutControllerGetMnemonicsModifiersMethodInfo,
#endif
shortcutControllerGetMnemonicsModifiers ,
#if defined(ENABLE_OVERLOADING)
ShortcutControllerGetScopeMethodInfo ,
#endif
shortcutControllerGetScope ,
shortcutControllerNew ,
shortcutControllerNewForModel ,
#if defined(ENABLE_OVERLOADING)
ShortcutControllerRemoveShortcutMethodInfo,
#endif
shortcutControllerRemoveShortcut ,
#if defined(ENABLE_OVERLOADING)
ShortcutControllerSetMnemonicsModifiersMethodInfo,
#endif
shortcutControllerSetMnemonicsModifiers ,
#if defined(ENABLE_OVERLOADING)
ShortcutControllerSetScopeMethodInfo ,
#endif
shortcutControllerSetScope ,
#if defined(ENABLE_OVERLOADING)
ShortcutControllerMnemonicModifiersPropertyInfo,
#endif
constructShortcutControllerMnemonicModifiers,
getShortcutControllerMnemonicModifiers ,
setShortcutControllerMnemonicModifiers ,
#if defined(ENABLE_OVERLOADING)
shortcutControllerMnemonicModifiers ,
#endif
#if defined(ENABLE_OVERLOADING)
ShortcutControllerModelPropertyInfo ,
#endif
constructShortcutControllerModel ,
#if defined(ENABLE_OVERLOADING)
shortcutControllerModel ,
#endif
#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.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified 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
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
/= :: ShortcutController -> ShortcutController -> Bool
$c/= :: ShortcutController -> ShortcutController -> Bool
== :: ShortcutController -> ShortcutController -> Bool
$c== :: 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
instance B.GValue.IsGValue ShortcutController where
toGValue :: ShortcutController -> IO GValue
toGValue ShortcutController
o = do
GType
gtype <- IO GType
c_gtk_shortcut_controller_get_type
ShortcutController
-> (Ptr ShortcutController -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ShortcutController
o (GType
-> (GValue -> Ptr ShortcutController -> IO ())
-> Ptr ShortcutController
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr ShortcutController -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO ShortcutController
fromGValue GValue
gv = do
Ptr ShortcutController
ptr <- GValue -> IO (Ptr ShortcutController)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr ShortcutController)
(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
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]
toShortcutController :: (MonadIO m, IsShortcutController o) => o -> m ShortcutController
toShortcutController :: o -> m ShortcutController
toShortcutController = IO ShortcutController -> m ShortcutController
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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'
unsafeCastTo ManagedPtr ShortcutController -> ShortcutController
ShortcutController
#if defined(ENABLE_OVERLOADING)
type family ResolveShortcutControllerMethod (t :: Symbol) (o :: *) :: * where
ResolveShortcutControllerMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
ResolveShortcutControllerMethod "addShortcut" o = ShortcutControllerAddShortcutMethodInfo
ResolveShortcutControllerMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveShortcutControllerMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveShortcutControllerMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
ResolveShortcutControllerMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
ResolveShortcutControllerMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
ResolveShortcutControllerMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
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 "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
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 "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 "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
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 "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
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 l o = O.MethodResolutionFailed l o
instance (info ~ ResolveShortcutControllerMethod t ShortcutController, O.MethodInfo 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
#endif
getShortcutControllerMnemonicModifiers :: (MonadIO m, IsShortcutController o) => o -> m [Gdk.Flags.ModifierType]
getShortcutControllerMnemonicModifiers :: o -> m [ModifierType]
getShortcutControllerMnemonicModifiers o
obj = IO [ModifierType] -> m [ModifierType]
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
$ 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"
setShortcutControllerMnemonicModifiers :: (MonadIO m, IsShortcutController o) => o -> [Gdk.Flags.ModifierType] -> m ()
setShortcutControllerMnemonicModifiers :: o -> [ModifierType] -> m ()
setShortcutControllerMnemonicModifiers o
obj [ModifierType]
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ 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
constructShortcutControllerMnemonicModifiers :: (IsShortcutController o, MIO.MonadIO m) => [Gdk.Flags.ModifierType] -> m (GValueConstruct o)
constructShortcutControllerMnemonicModifiers :: [ModifierType] -> m (GValueConstruct o)
constructShortcutControllerMnemonicModifiers [ModifierType]
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#endif
constructShortcutControllerModel :: (IsShortcutController o, MIO.MonadIO m, Gio.ListModel.IsListModel a) => a -> m (GValueConstruct o)
constructShortcutControllerModel :: a -> m (GValueConstruct o)
constructShortcutControllerModel a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#endif
getShortcutControllerScope :: (MonadIO m, IsShortcutController o) => o -> m Gtk.Enums.ShortcutScope
getShortcutControllerScope :: o -> m ShortcutScope
getShortcutControllerScope o
obj = IO ShortcutScope -> m ShortcutScope
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
$ o -> String -> IO ShortcutScope
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"scope"
setShortcutControllerScope :: (MonadIO m, IsShortcutController o) => o -> Gtk.Enums.ShortcutScope -> m ()
setShortcutControllerScope :: o -> ShortcutScope -> m ()
setShortcutControllerScope o
obj ShortcutScope
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ 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
constructShortcutControllerScope :: (IsShortcutController o, MIO.MonadIO m) => Gtk.Enums.ShortcutScope -> m (GValueConstruct o)
constructShortcutControllerScope :: ShortcutScope -> m (GValueConstruct o)
constructShortcutControllerScope ShortcutScope
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ShortcutController
type instance O.AttributeList ShortcutController = ShortcutControllerAttributeList
type ShortcutControllerAttributeList = ('[ '("mnemonicModifiers", ShortcutControllerMnemonicModifiersPropertyInfo), '("model", ShortcutControllerModelPropertyInfo), '("name", Gtk.EventController.EventControllerNamePropertyInfo), '("propagationLimit", Gtk.EventController.EventControllerPropagationLimitPropertyInfo), '("propagationPhase", Gtk.EventController.EventControllerPropagationPhasePropertyInfo), '("scope", ShortcutControllerScopePropertyInfo), '("widget", Gtk.EventController.EventControllerWidgetPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
shortcutControllerMnemonicModifiers :: AttrLabelProxy "mnemonicModifiers"
shortcutControllerMnemonicModifiers = AttrLabelProxy
shortcutControllerModel :: AttrLabelProxy "model"
shortcutControllerModel = 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
foreign import ccall "gtk_shortcut_controller_new" gtk_shortcut_controller_new ::
IO (Ptr ShortcutController)
shortcutControllerNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m ShortcutController
shortcutControllerNew :: m ShortcutController
shortcutControllerNew = IO ShortcutController -> m ShortcutController
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 (m :: * -> *) a. Monad m => a -> m a
return ShortcutController
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_shortcut_controller_new_for_model" gtk_shortcut_controller_new_for_model ::
Ptr Gio.ListModel.ListModel ->
IO (Ptr ShortcutController)
shortcutControllerNewForModel ::
(B.CallStack.HasCallStack, MonadIO m, Gio.ListModel.IsListModel a) =>
a
-> m ShortcutController
shortcutControllerNewForModel :: a -> m ShortcutController
shortcutControllerNewForModel a
model = IO ShortcutController -> m ShortcutController
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 (m :: * -> *) a. Monad m => a -> m a
return ShortcutController
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_shortcut_controller_add_shortcut" gtk_shortcut_controller_add_shortcut ::
Ptr ShortcutController ->
Ptr Gtk.Shortcut.Shortcut ->
IO ()
shortcutControllerAddShortcut ::
(B.CallStack.HasCallStack, MonadIO m, IsShortcutController a, Gtk.Shortcut.IsShortcut b) =>
a
-> b
-> m ()
shortcutControllerAddShortcut :: a -> b -> m ()
shortcutControllerAddShortcut a
self b
shortcut = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (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.MethodInfo ShortcutControllerAddShortcutMethodInfo a signature where
overloadedMethod = shortcutControllerAddShortcut
#endif
foreign import ccall "gtk_shortcut_controller_get_mnemonics_modifiers" gtk_shortcut_controller_get_mnemonics_modifiers ::
Ptr ShortcutController ->
IO CUInt
shortcutControllerGetMnemonicsModifiers ::
(B.CallStack.HasCallStack, MonadIO m, IsShortcutController a) =>
a
-> m [Gdk.Flags.ModifierType]
shortcutControllerGetMnemonicsModifiers :: a -> m [ModifierType]
shortcutControllerGetMnemonicsModifiers a
self = IO [ModifierType] -> m [ModifierType]
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 (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.MethodInfo ShortcutControllerGetMnemonicsModifiersMethodInfo a signature where
overloadedMethod = shortcutControllerGetMnemonicsModifiers
#endif
foreign import ccall "gtk_shortcut_controller_get_scope" gtk_shortcut_controller_get_scope ::
Ptr ShortcutController ->
IO CUInt
shortcutControllerGetScope ::
(B.CallStack.HasCallStack, MonadIO m, IsShortcutController a) =>
a
-> m Gtk.Enums.ShortcutScope
shortcutControllerGetScope :: a -> m ShortcutScope
shortcutControllerGetScope a
self = IO ShortcutScope -> m ShortcutScope
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 (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.MethodInfo ShortcutControllerGetScopeMethodInfo a signature where
overloadedMethod = shortcutControllerGetScope
#endif
foreign import ccall "gtk_shortcut_controller_remove_shortcut" gtk_shortcut_controller_remove_shortcut ::
Ptr ShortcutController ->
Ptr Gtk.Shortcut.Shortcut ->
IO ()
shortcutControllerRemoveShortcut ::
(B.CallStack.HasCallStack, MonadIO m, IsShortcutController a, Gtk.Shortcut.IsShortcut b) =>
a
-> b
-> m ()
shortcutControllerRemoveShortcut :: a -> b -> m ()
shortcutControllerRemoveShortcut a
self b
shortcut = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (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.MethodInfo ShortcutControllerRemoveShortcutMethodInfo a signature where
overloadedMethod = shortcutControllerRemoveShortcut
#endif
foreign import ccall "gtk_shortcut_controller_set_mnemonics_modifiers" gtk_shortcut_controller_set_mnemonics_modifiers ::
Ptr ShortcutController ->
CUInt ->
IO ()
shortcutControllerSetMnemonicsModifiers ::
(B.CallStack.HasCallStack, MonadIO m, IsShortcutController a) =>
a
-> [Gdk.Flags.ModifierType]
-> m ()
shortcutControllerSetMnemonicsModifiers :: a -> [ModifierType] -> m ()
shortcutControllerSetMnemonicsModifiers a
self [ModifierType]
modifiers = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (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.MethodInfo ShortcutControllerSetMnemonicsModifiersMethodInfo a signature where
overloadedMethod = shortcutControllerSetMnemonicsModifiers
#endif
foreign import ccall "gtk_shortcut_controller_set_scope" gtk_shortcut_controller_set_scope ::
Ptr ShortcutController ->
CUInt ->
IO ()
shortcutControllerSetScope ::
(B.CallStack.HasCallStack, MonadIO m, IsShortcutController a) =>
a
-> Gtk.Enums.ShortcutScope
-> m ()
shortcutControllerSetScope :: a -> ShortcutScope -> m ()
shortcutControllerSetScope a
self ShortcutScope
scope = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (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.MethodInfo ShortcutControllerSetScopeMethodInfo a signature where
overloadedMethod = shortcutControllerSetScope
#endif