{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Dazzle.Objects.ShortcutModel
(
ShortcutModel(..) ,
IsShortcutModel ,
toShortcutModel ,
#if defined(ENABLE_OVERLOADING)
ResolveShortcutModelMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ShortcutModelGetManagerMethodInfo ,
#endif
shortcutModelGetManager ,
#if defined(ENABLE_OVERLOADING)
ShortcutModelGetThemeMethodInfo ,
#endif
shortcutModelGetTheme ,
shortcutModelNew ,
#if defined(ENABLE_OVERLOADING)
ShortcutModelRebuildMethodInfo ,
#endif
shortcutModelRebuild ,
#if defined(ENABLE_OVERLOADING)
ShortcutModelSetChordMethodInfo ,
#endif
shortcutModelSetChord ,
#if defined(ENABLE_OVERLOADING)
ShortcutModelSetManagerMethodInfo ,
#endif
shortcutModelSetManager ,
#if defined(ENABLE_OVERLOADING)
ShortcutModelSetThemeMethodInfo ,
#endif
shortcutModelSetTheme ,
#if defined(ENABLE_OVERLOADING)
ShortcutModelManagerPropertyInfo ,
#endif
constructShortcutModelManager ,
getShortcutModelManager ,
setShortcutModelManager ,
#if defined(ENABLE_OVERLOADING)
shortcutModelManager ,
#endif
#if defined(ENABLE_OVERLOADING)
ShortcutModelThemePropertyInfo ,
#endif
constructShortcutModelTheme ,
getShortcutModelTheme ,
setShortcutModelTheme ,
#if defined(ENABLE_OVERLOADING)
shortcutModelTheme ,
#endif
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.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.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import {-# SOURCE #-} qualified GI.Dazzle.Enums as Dazzle.Enums
import {-# SOURCE #-} qualified GI.Dazzle.Flags as Dazzle.Flags
import {-# SOURCE #-} qualified GI.Dazzle.Objects.ShortcutContext as Dazzle.ShortcutContext
import {-# SOURCE #-} qualified GI.Dazzle.Objects.ShortcutManager as Dazzle.ShortcutManager
import {-# SOURCE #-} qualified GI.Dazzle.Objects.ShortcutTheme as Dazzle.ShortcutTheme
import {-# SOURCE #-} qualified GI.Dazzle.Objects.ShortcutsWindow as Dazzle.ShortcutsWindow
import {-# SOURCE #-} qualified GI.Dazzle.Structs.ShortcutChord as Dazzle.ShortcutChord
import {-# SOURCE #-} qualified GI.Dazzle.Structs.ShortcutEntry as Dazzle.ShortcutEntry
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Flags as Gdk.Flags
import qualified GI.Gdk.Structs.EventKey as Gdk.EventKey
import qualified GI.Gio.Interfaces.File as Gio.File
import qualified GI.Gio.Interfaces.Initable as Gio.Initable
import qualified GI.Gio.Interfaces.ListModel as Gio.ListModel
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import qualified GI.Gio.Objects.OutputStream as Gio.OutputStream
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Interfaces.TreeDragDest as Gtk.TreeDragDest
import qualified GI.Gtk.Interfaces.TreeDragSource as Gtk.TreeDragSource
import qualified GI.Gtk.Interfaces.TreeModel as Gtk.TreeModel
import qualified GI.Gtk.Interfaces.TreeSortable as Gtk.TreeSortable
import qualified GI.Gtk.Objects.Bin as Gtk.Bin
import qualified GI.Gtk.Objects.Container as Gtk.Container
import qualified GI.Gtk.Objects.TreeStore as Gtk.TreeStore
import qualified GI.Gtk.Objects.Widget as Gtk.Widget
import qualified GI.Gtk.Objects.Window as Gtk.Window
import qualified GI.Gtk.Structs.TreeIter as Gtk.TreeIter
#else
import {-# SOURCE #-} qualified GI.Dazzle.Objects.ShortcutManager as Dazzle.ShortcutManager
import {-# SOURCE #-} qualified GI.Dazzle.Objects.ShortcutTheme as Dazzle.ShortcutTheme
import {-# SOURCE #-} qualified GI.Dazzle.Structs.ShortcutChord as Dazzle.ShortcutChord
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Interfaces.TreeDragDest as Gtk.TreeDragDest
import qualified GI.Gtk.Interfaces.TreeDragSource as Gtk.TreeDragSource
import qualified GI.Gtk.Interfaces.TreeModel as Gtk.TreeModel
import qualified GI.Gtk.Interfaces.TreeSortable as Gtk.TreeSortable
import qualified GI.Gtk.Objects.TreeStore as Gtk.TreeStore
import qualified GI.Gtk.Structs.TreeIter as Gtk.TreeIter
#endif
newtype ShortcutModel = ShortcutModel (SP.ManagedPtr ShortcutModel)
deriving (ShortcutModel -> ShortcutModel -> Bool
(ShortcutModel -> ShortcutModel -> Bool)
-> (ShortcutModel -> ShortcutModel -> Bool) -> Eq ShortcutModel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ShortcutModel -> ShortcutModel -> Bool
== :: ShortcutModel -> ShortcutModel -> Bool
$c/= :: ShortcutModel -> ShortcutModel -> Bool
/= :: ShortcutModel -> ShortcutModel -> Bool
Eq)
instance SP.ManagedPtrNewtype ShortcutModel where
toManagedPtr :: ShortcutModel -> ManagedPtr ShortcutModel
toManagedPtr (ShortcutModel ManagedPtr ShortcutModel
p) = ManagedPtr ShortcutModel
p
foreign import ccall "dzl_shortcut_model_get_type"
c_dzl_shortcut_model_get_type :: IO B.Types.GType
instance B.Types.TypedObject ShortcutModel where
glibType :: IO GType
glibType = IO GType
c_dzl_shortcut_model_get_type
instance B.Types.GObject ShortcutModel
class (SP.GObject o, O.IsDescendantOf ShortcutModel o) => IsShortcutModel o
instance (SP.GObject o, O.IsDescendantOf ShortcutModel o) => IsShortcutModel o
instance O.HasParentTypes ShortcutModel
type instance O.ParentTypes ShortcutModel = '[Gtk.TreeStore.TreeStore, GObject.Object.Object, Gtk.Buildable.Buildable, Gtk.TreeDragDest.TreeDragDest, Gtk.TreeDragSource.TreeDragSource, Gtk.TreeModel.TreeModel, Gtk.TreeSortable.TreeSortable]
toShortcutModel :: (MIO.MonadIO m, IsShortcutModel o) => o -> m ShortcutModel
toShortcutModel :: forall (m :: * -> *) o.
(MonadIO m, IsShortcutModel o) =>
o -> m ShortcutModel
toShortcutModel = IO ShortcutModel -> m ShortcutModel
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO ShortcutModel -> m ShortcutModel)
-> (o -> IO ShortcutModel) -> o -> m ShortcutModel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr ShortcutModel -> ShortcutModel)
-> o -> IO ShortcutModel
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr ShortcutModel -> ShortcutModel
ShortcutModel
instance B.GValue.IsGValue (Maybe ShortcutModel) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_dzl_shortcut_model_get_type
gvalueSet_ :: Ptr GValue -> Maybe ShortcutModel -> IO ()
gvalueSet_ Ptr GValue
gv Maybe ShortcutModel
P.Nothing = Ptr GValue -> Ptr ShortcutModel -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr ShortcutModel
forall a. Ptr a
FP.nullPtr :: FP.Ptr ShortcutModel)
gvalueSet_ Ptr GValue
gv (P.Just ShortcutModel
obj) = ShortcutModel -> (Ptr ShortcutModel -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ShortcutModel
obj (Ptr GValue -> Ptr ShortcutModel -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe ShortcutModel)
gvalueGet_ Ptr GValue
gv = do
Ptr ShortcutModel
ptr <- Ptr GValue -> IO (Ptr ShortcutModel)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr ShortcutModel)
if Ptr ShortcutModel
ptr Ptr ShortcutModel -> Ptr ShortcutModel -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr ShortcutModel
forall a. Ptr a
FP.nullPtr
then ShortcutModel -> Maybe ShortcutModel
forall a. a -> Maybe a
P.Just (ShortcutModel -> Maybe ShortcutModel)
-> IO ShortcutModel -> IO (Maybe ShortcutModel)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr ShortcutModel -> ShortcutModel)
-> Ptr ShortcutModel -> IO ShortcutModel
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr ShortcutModel -> ShortcutModel
ShortcutModel Ptr ShortcutModel
ptr
else Maybe ShortcutModel -> IO (Maybe ShortcutModel)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ShortcutModel
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveShortcutModelMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveShortcutModelMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
ResolveShortcutModelMethod "append" o = Gtk.TreeStore.TreeStoreAppendMethodInfo
ResolveShortcutModelMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveShortcutModelMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveShortcutModelMethod "clear" o = Gtk.TreeStore.TreeStoreClearMethodInfo
ResolveShortcutModelMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
ResolveShortcutModelMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
ResolveShortcutModelMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
ResolveShortcutModelMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
ResolveShortcutModelMethod "dragDataDelete" o = Gtk.TreeDragSource.TreeDragSourceDragDataDeleteMethodInfo
ResolveShortcutModelMethod "dragDataGet" o = Gtk.TreeDragSource.TreeDragSourceDragDataGetMethodInfo
ResolveShortcutModelMethod "dragDataReceived" o = Gtk.TreeDragDest.TreeDragDestDragDataReceivedMethodInfo
ResolveShortcutModelMethod "filterNew" o = Gtk.TreeModel.TreeModelFilterNewMethodInfo
ResolveShortcutModelMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveShortcutModelMethod "foreach" o = Gtk.TreeModel.TreeModelForeachMethodInfo
ResolveShortcutModelMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveShortcutModelMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveShortcutModelMethod "hasDefaultSortFunc" o = Gtk.TreeSortable.TreeSortableHasDefaultSortFuncMethodInfo
ResolveShortcutModelMethod "insert" o = Gtk.TreeStore.TreeStoreInsertMethodInfo
ResolveShortcutModelMethod "insertAfter" o = Gtk.TreeStore.TreeStoreInsertAfterMethodInfo
ResolveShortcutModelMethod "insertBefore" o = Gtk.TreeStore.TreeStoreInsertBeforeMethodInfo
ResolveShortcutModelMethod "insertWithValues" o = Gtk.TreeStore.TreeStoreInsertWithValuesMethodInfo
ResolveShortcutModelMethod "isAncestor" o = Gtk.TreeStore.TreeStoreIsAncestorMethodInfo
ResolveShortcutModelMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveShortcutModelMethod "iterChildren" o = Gtk.TreeModel.TreeModelIterChildrenMethodInfo
ResolveShortcutModelMethod "iterDepth" o = Gtk.TreeStore.TreeStoreIterDepthMethodInfo
ResolveShortcutModelMethod "iterHasChild" o = Gtk.TreeModel.TreeModelIterHasChildMethodInfo
ResolveShortcutModelMethod "iterIsValid" o = Gtk.TreeStore.TreeStoreIterIsValidMethodInfo
ResolveShortcutModelMethod "iterNChildren" o = Gtk.TreeModel.TreeModelIterNChildrenMethodInfo
ResolveShortcutModelMethod "iterNext" o = Gtk.TreeModel.TreeModelIterNextMethodInfo
ResolveShortcutModelMethod "iterNthChild" o = Gtk.TreeModel.TreeModelIterNthChildMethodInfo
ResolveShortcutModelMethod "iterParent" o = Gtk.TreeModel.TreeModelIterParentMethodInfo
ResolveShortcutModelMethod "iterPrevious" o = Gtk.TreeModel.TreeModelIterPreviousMethodInfo
ResolveShortcutModelMethod "moveAfter" o = Gtk.TreeStore.TreeStoreMoveAfterMethodInfo
ResolveShortcutModelMethod "moveBefore" o = Gtk.TreeStore.TreeStoreMoveBeforeMethodInfo
ResolveShortcutModelMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveShortcutModelMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveShortcutModelMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
ResolveShortcutModelMethod "prepend" o = Gtk.TreeStore.TreeStorePrependMethodInfo
ResolveShortcutModelMethod "rebuild" o = ShortcutModelRebuildMethodInfo
ResolveShortcutModelMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveShortcutModelMethod "refNode" o = Gtk.TreeModel.TreeModelRefNodeMethodInfo
ResolveShortcutModelMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveShortcutModelMethod "remove" o = Gtk.TreeStore.TreeStoreRemoveMethodInfo
ResolveShortcutModelMethod "rowChanged" o = Gtk.TreeModel.TreeModelRowChangedMethodInfo
ResolveShortcutModelMethod "rowDeleted" o = Gtk.TreeModel.TreeModelRowDeletedMethodInfo
ResolveShortcutModelMethod "rowDraggable" o = Gtk.TreeDragSource.TreeDragSourceRowDraggableMethodInfo
ResolveShortcutModelMethod "rowDropPossible" o = Gtk.TreeDragDest.TreeDragDestRowDropPossibleMethodInfo
ResolveShortcutModelMethod "rowHasChildToggled" o = Gtk.TreeModel.TreeModelRowHasChildToggledMethodInfo
ResolveShortcutModelMethod "rowInserted" o = Gtk.TreeModel.TreeModelRowInsertedMethodInfo
ResolveShortcutModelMethod "rowsReordered" o = Gtk.TreeModel.TreeModelRowsReorderedMethodInfo
ResolveShortcutModelMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveShortcutModelMethod "set" o = Gtk.TreeStore.TreeStoreSetMethodInfo
ResolveShortcutModelMethod "sortColumnChanged" o = Gtk.TreeSortable.TreeSortableSortColumnChangedMethodInfo
ResolveShortcutModelMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveShortcutModelMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveShortcutModelMethod "swap" o = Gtk.TreeStore.TreeStoreSwapMethodInfo
ResolveShortcutModelMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveShortcutModelMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveShortcutModelMethod "unrefNode" o = Gtk.TreeModel.TreeModelUnrefNodeMethodInfo
ResolveShortcutModelMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveShortcutModelMethod "getColumnType" o = Gtk.TreeModel.TreeModelGetColumnTypeMethodInfo
ResolveShortcutModelMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveShortcutModelMethod "getFlags" o = Gtk.TreeModel.TreeModelGetFlagsMethodInfo
ResolveShortcutModelMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
ResolveShortcutModelMethod "getIter" o = Gtk.TreeModel.TreeModelGetIterMethodInfo
ResolveShortcutModelMethod "getIterFirst" o = Gtk.TreeModel.TreeModelGetIterFirstMethodInfo
ResolveShortcutModelMethod "getIterFromString" o = Gtk.TreeModel.TreeModelGetIterFromStringMethodInfo
ResolveShortcutModelMethod "getManager" o = ShortcutModelGetManagerMethodInfo
ResolveShortcutModelMethod "getNColumns" o = Gtk.TreeModel.TreeModelGetNColumnsMethodInfo
ResolveShortcutModelMethod "getName" o = Gtk.Buildable.BuildableGetNameMethodInfo
ResolveShortcutModelMethod "getPath" o = Gtk.TreeModel.TreeModelGetPathMethodInfo
ResolveShortcutModelMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveShortcutModelMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveShortcutModelMethod "getSortColumnId" o = Gtk.TreeSortable.TreeSortableGetSortColumnIdMethodInfo
ResolveShortcutModelMethod "getStringFromIter" o = Gtk.TreeModel.TreeModelGetStringFromIterMethodInfo
ResolveShortcutModelMethod "getTheme" o = ShortcutModelGetThemeMethodInfo
ResolveShortcutModelMethod "getValue" o = Gtk.TreeModel.TreeModelGetValueMethodInfo
ResolveShortcutModelMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
ResolveShortcutModelMethod "setChord" o = ShortcutModelSetChordMethodInfo
ResolveShortcutModelMethod "setColumnTypes" o = Gtk.TreeStore.TreeStoreSetColumnTypesMethodInfo
ResolveShortcutModelMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveShortcutModelMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveShortcutModelMethod "setDefaultSortFunc" o = Gtk.TreeSortable.TreeSortableSetDefaultSortFuncMethodInfo
ResolveShortcutModelMethod "setManager" o = ShortcutModelSetManagerMethodInfo
ResolveShortcutModelMethod "setName" o = Gtk.Buildable.BuildableSetNameMethodInfo
ResolveShortcutModelMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveShortcutModelMethod "setSortColumnId" o = Gtk.TreeSortable.TreeSortableSetSortColumnIdMethodInfo
ResolveShortcutModelMethod "setSortFunc" o = Gtk.TreeSortable.TreeSortableSetSortFuncMethodInfo
ResolveShortcutModelMethod "setTheme" o = ShortcutModelSetThemeMethodInfo
ResolveShortcutModelMethod "setValue" o = Gtk.TreeStore.TreeStoreSetValueMethodInfo
ResolveShortcutModelMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveShortcutModelMethod t ShortcutModel, O.OverloadedMethod info ShortcutModel p) => OL.IsLabel t (ShortcutModel -> 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 ~ ResolveShortcutModelMethod t ShortcutModel, O.OverloadedMethod info ShortcutModel p, R.HasField t ShortcutModel p) => R.HasField t ShortcutModel p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveShortcutModelMethod t ShortcutModel, O.OverloadedMethodInfo info ShortcutModel) => OL.IsLabel t (O.MethodProxy info ShortcutModel) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
getShortcutModelManager :: (MonadIO m, IsShortcutModel o) => o -> m Dazzle.ShortcutManager.ShortcutManager
getShortcutModelManager :: forall (m :: * -> *) o.
(MonadIO m, IsShortcutModel o) =>
o -> m ShortcutManager
getShortcutModelManager o
obj = IO ShortcutManager -> m ShortcutManager
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO ShortcutManager -> m ShortcutManager)
-> IO ShortcutManager -> m ShortcutManager
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe ShortcutManager) -> IO ShortcutManager
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getShortcutModelManager" (IO (Maybe ShortcutManager) -> IO ShortcutManager)
-> IO (Maybe ShortcutManager) -> IO ShortcutManager
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr ShortcutManager -> ShortcutManager)
-> IO (Maybe ShortcutManager)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"manager" ManagedPtr ShortcutManager -> ShortcutManager
Dazzle.ShortcutManager.ShortcutManager
setShortcutModelManager :: (MonadIO m, IsShortcutModel o, Dazzle.ShortcutManager.IsShortcutManager a) => o -> a -> m ()
setShortcutModelManager :: forall (m :: * -> *) o a.
(MonadIO m, IsShortcutModel o, IsShortcutManager a) =>
o -> a -> m ()
setShortcutModelManager o
obj a
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"manager" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructShortcutModelManager :: (IsShortcutModel o, MIO.MonadIO m, Dazzle.ShortcutManager.IsShortcutManager a) => a -> m (GValueConstruct o)
constructShortcutModelManager :: forall o (m :: * -> *) a.
(IsShortcutModel o, MonadIO m, IsShortcutManager a) =>
a -> m (GValueConstruct o)
constructShortcutModelManager a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"manager" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data ShortcutModelManagerPropertyInfo
instance AttrInfo ShortcutModelManagerPropertyInfo where
type AttrAllowedOps ShortcutModelManagerPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ShortcutModelManagerPropertyInfo = IsShortcutModel
type AttrSetTypeConstraint ShortcutModelManagerPropertyInfo = Dazzle.ShortcutManager.IsShortcutManager
type AttrTransferTypeConstraint ShortcutModelManagerPropertyInfo = Dazzle.ShortcutManager.IsShortcutManager
type AttrTransferType ShortcutModelManagerPropertyInfo = Dazzle.ShortcutManager.ShortcutManager
type AttrGetType ShortcutModelManagerPropertyInfo = Dazzle.ShortcutManager.ShortcutManager
type AttrLabel ShortcutModelManagerPropertyInfo = "manager"
type AttrOrigin ShortcutModelManagerPropertyInfo = ShortcutModel
attrGet = getShortcutModelManager
attrSet = setShortcutModelManager
attrTransfer _ v = do
unsafeCastTo Dazzle.ShortcutManager.ShortcutManager v
attrConstruct = constructShortcutModelManager
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.ShortcutModel.manager"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-ShortcutModel.html#g:attr:manager"
})
#endif
getShortcutModelTheme :: (MonadIO m, IsShortcutModel o) => o -> m Dazzle.ShortcutTheme.ShortcutTheme
getShortcutModelTheme :: forall (m :: * -> *) o.
(MonadIO m, IsShortcutModel o) =>
o -> m ShortcutTheme
getShortcutModelTheme o
obj = IO ShortcutTheme -> m ShortcutTheme
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO ShortcutTheme -> m ShortcutTheme)
-> IO ShortcutTheme -> m ShortcutTheme
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe ShortcutTheme) -> IO ShortcutTheme
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getShortcutModelTheme" (IO (Maybe ShortcutTheme) -> IO ShortcutTheme)
-> IO (Maybe ShortcutTheme) -> IO ShortcutTheme
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr ShortcutTheme -> ShortcutTheme)
-> IO (Maybe ShortcutTheme)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"theme" ManagedPtr ShortcutTheme -> ShortcutTheme
Dazzle.ShortcutTheme.ShortcutTheme
setShortcutModelTheme :: (MonadIO m, IsShortcutModel o, Dazzle.ShortcutTheme.IsShortcutTheme a) => o -> a -> m ()
setShortcutModelTheme :: forall (m :: * -> *) o a.
(MonadIO m, IsShortcutModel o, IsShortcutTheme a) =>
o -> a -> m ()
setShortcutModelTheme o
obj a
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"theme" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructShortcutModelTheme :: (IsShortcutModel o, MIO.MonadIO m, Dazzle.ShortcutTheme.IsShortcutTheme a) => a -> m (GValueConstruct o)
constructShortcutModelTheme :: forall o (m :: * -> *) a.
(IsShortcutModel o, MonadIO m, IsShortcutTheme a) =>
a -> m (GValueConstruct o)
constructShortcutModelTheme a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"theme" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data ShortcutModelThemePropertyInfo
instance AttrInfo ShortcutModelThemePropertyInfo where
type AttrAllowedOps ShortcutModelThemePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ShortcutModelThemePropertyInfo = IsShortcutModel
type AttrSetTypeConstraint ShortcutModelThemePropertyInfo = Dazzle.ShortcutTheme.IsShortcutTheme
type AttrTransferTypeConstraint ShortcutModelThemePropertyInfo = Dazzle.ShortcutTheme.IsShortcutTheme
type AttrTransferType ShortcutModelThemePropertyInfo = Dazzle.ShortcutTheme.ShortcutTheme
type AttrGetType ShortcutModelThemePropertyInfo = Dazzle.ShortcutTheme.ShortcutTheme
type AttrLabel ShortcutModelThemePropertyInfo = "theme"
type AttrOrigin ShortcutModelThemePropertyInfo = ShortcutModel
attrGet = getShortcutModelTheme
attrSet = setShortcutModelTheme
attrTransfer _ v = do
unsafeCastTo Dazzle.ShortcutTheme.ShortcutTheme v
attrConstruct = constructShortcutModelTheme
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.ShortcutModel.theme"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-ShortcutModel.html#g:attr:theme"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ShortcutModel
type instance O.AttributeList ShortcutModel = ShortcutModelAttributeList
type ShortcutModelAttributeList = ('[ '("manager", ShortcutModelManagerPropertyInfo), '("theme", ShortcutModelThemePropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
shortcutModelManager :: AttrLabelProxy "manager"
shortcutModelManager = AttrLabelProxy
shortcutModelTheme :: AttrLabelProxy "theme"
shortcutModelTheme = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ShortcutModel = ShortcutModelSignalList
type ShortcutModelSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo), '("rowChanged", Gtk.TreeModel.TreeModelRowChangedSignalInfo), '("rowDeleted", Gtk.TreeModel.TreeModelRowDeletedSignalInfo), '("rowHasChildToggled", Gtk.TreeModel.TreeModelRowHasChildToggledSignalInfo), '("rowInserted", Gtk.TreeModel.TreeModelRowInsertedSignalInfo), '("sortColumnChanged", Gtk.TreeSortable.TreeSortableSortColumnChangedSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "dzl_shortcut_model_get_manager" dzl_shortcut_model_get_manager ::
Ptr ShortcutModel ->
IO (Ptr Dazzle.ShortcutManager.ShortcutManager)
shortcutModelGetManager ::
(B.CallStack.HasCallStack, MonadIO m, IsShortcutModel a) =>
a
-> m Dazzle.ShortcutManager.ShortcutManager
shortcutModelGetManager :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsShortcutModel a) =>
a -> m ShortcutManager
shortcutModelGetManager a
self = IO ShortcutManager -> m ShortcutManager
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ShortcutManager -> m ShortcutManager)
-> IO ShortcutManager -> m ShortcutManager
forall a b. (a -> b) -> a -> b
$ do
Ptr ShortcutModel
self' <- a -> IO (Ptr ShortcutModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr ShortcutManager
result <- Ptr ShortcutModel -> IO (Ptr ShortcutManager)
dzl_shortcut_model_get_manager Ptr ShortcutModel
self'
Text -> Ptr ShortcutManager -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"shortcutModelGetManager" Ptr ShortcutManager
result
ShortcutManager
result' <- ((ManagedPtr ShortcutManager -> ShortcutManager)
-> Ptr ShortcutManager -> IO ShortcutManager
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr ShortcutManager -> ShortcutManager
Dazzle.ShortcutManager.ShortcutManager) Ptr ShortcutManager
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
ShortcutManager -> IO ShortcutManager
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ShortcutManager
result'
#if defined(ENABLE_OVERLOADING)
data ShortcutModelGetManagerMethodInfo
instance (signature ~ (m Dazzle.ShortcutManager.ShortcutManager), MonadIO m, IsShortcutModel a) => O.OverloadedMethod ShortcutModelGetManagerMethodInfo a signature where
overloadedMethod = shortcutModelGetManager
instance O.OverloadedMethodInfo ShortcutModelGetManagerMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.ShortcutModel.shortcutModelGetManager",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-ShortcutModel.html#v:shortcutModelGetManager"
})
#endif
foreign import ccall "dzl_shortcut_model_get_theme" dzl_shortcut_model_get_theme ::
Ptr ShortcutModel ->
IO (Ptr Dazzle.ShortcutTheme.ShortcutTheme)
shortcutModelGetTheme ::
(B.CallStack.HasCallStack, MonadIO m, IsShortcutModel a) =>
a
-> m Dazzle.ShortcutTheme.ShortcutTheme
shortcutModelGetTheme :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsShortcutModel a) =>
a -> m ShortcutTheme
shortcutModelGetTheme a
self = IO ShortcutTheme -> m ShortcutTheme
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ShortcutTheme -> m ShortcutTheme)
-> IO ShortcutTheme -> m ShortcutTheme
forall a b. (a -> b) -> a -> b
$ do
Ptr ShortcutModel
self' <- a -> IO (Ptr ShortcutModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr ShortcutTheme
result <- Ptr ShortcutModel -> IO (Ptr ShortcutTheme)
dzl_shortcut_model_get_theme Ptr ShortcutModel
self'
Text -> Ptr ShortcutTheme -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"shortcutModelGetTheme" Ptr ShortcutTheme
result
ShortcutTheme
result' <- ((ManagedPtr ShortcutTheme -> ShortcutTheme)
-> Ptr ShortcutTheme -> IO ShortcutTheme
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr ShortcutTheme -> ShortcutTheme
Dazzle.ShortcutTheme.ShortcutTheme) Ptr ShortcutTheme
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
ShortcutTheme -> IO ShortcutTheme
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ShortcutTheme
result'
#if defined(ENABLE_OVERLOADING)
data ShortcutModelGetThemeMethodInfo
instance (signature ~ (m Dazzle.ShortcutTheme.ShortcutTheme), MonadIO m, IsShortcutModel a) => O.OverloadedMethod ShortcutModelGetThemeMethodInfo a signature where
overloadedMethod = shortcutModelGetTheme
instance O.OverloadedMethodInfo ShortcutModelGetThemeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.ShortcutModel.shortcutModelGetTheme",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-ShortcutModel.html#v:shortcutModelGetTheme"
})
#endif
foreign import ccall "dzl_shortcut_model_rebuild" dzl_shortcut_model_rebuild ::
Ptr ShortcutModel ->
IO ()
shortcutModelRebuild ::
(B.CallStack.HasCallStack, MonadIO m, IsShortcutModel a) =>
a
-> m ()
shortcutModelRebuild :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsShortcutModel a) =>
a -> m ()
shortcutModelRebuild a
self = 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 ShortcutModel
self' <- a -> IO (Ptr ShortcutModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr ShortcutModel -> IO ()
dzl_shortcut_model_rebuild Ptr ShortcutModel
self'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ShortcutModelRebuildMethodInfo
instance (signature ~ (m ()), MonadIO m, IsShortcutModel a) => O.OverloadedMethod ShortcutModelRebuildMethodInfo a signature where
overloadedMethod = shortcutModelRebuild
instance O.OverloadedMethodInfo ShortcutModelRebuildMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.ShortcutModel.shortcutModelRebuild",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-ShortcutModel.html#v:shortcutModelRebuild"
})
#endif
foreign import ccall "dzl_shortcut_model_set_chord" dzl_shortcut_model_set_chord ::
Ptr ShortcutModel ->
Ptr Gtk.TreeIter.TreeIter ->
Ptr Dazzle.ShortcutChord.ShortcutChord ->
IO ()
shortcutModelSetChord ::
(B.CallStack.HasCallStack, MonadIO m, IsShortcutModel a) =>
a
-> Gtk.TreeIter.TreeIter
-> Dazzle.ShortcutChord.ShortcutChord
-> m ()
shortcutModelSetChord :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsShortcutModel a) =>
a -> TreeIter -> ShortcutChord -> m ()
shortcutModelSetChord a
self TreeIter
iter ShortcutChord
chord = 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 ShortcutModel
self' <- a -> IO (Ptr ShortcutModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr TreeIter
iter' <- TreeIter -> IO (Ptr TreeIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreeIter
iter
Ptr ShortcutChord
chord' <- ShortcutChord -> IO (Ptr ShortcutChord)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ShortcutChord
chord
Ptr ShortcutModel -> Ptr TreeIter -> Ptr ShortcutChord -> IO ()
dzl_shortcut_model_set_chord Ptr ShortcutModel
self' Ptr TreeIter
iter' Ptr ShortcutChord
chord'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
TreeIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreeIter
iter
ShortcutChord -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr ShortcutChord
chord
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ShortcutModelSetChordMethodInfo
instance (signature ~ (Gtk.TreeIter.TreeIter -> Dazzle.ShortcutChord.ShortcutChord -> m ()), MonadIO m, IsShortcutModel a) => O.OverloadedMethod ShortcutModelSetChordMethodInfo a signature where
overloadedMethod = shortcutModelSetChord
instance O.OverloadedMethodInfo ShortcutModelSetChordMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.ShortcutModel.shortcutModelSetChord",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-ShortcutModel.html#v:shortcutModelSetChord"
})
#endif
foreign import ccall "dzl_shortcut_model_set_manager" dzl_shortcut_model_set_manager ::
Ptr ShortcutModel ->
Ptr Dazzle.ShortcutManager.ShortcutManager ->
IO ()
shortcutModelSetManager ::
(B.CallStack.HasCallStack, MonadIO m, IsShortcutModel a, Dazzle.ShortcutManager.IsShortcutManager b) =>
a
-> b
-> m ()
shortcutModelSetManager :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsShortcutModel a,
IsShortcutManager b) =>
a -> b -> m ()
shortcutModelSetManager a
self b
manager = 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 ShortcutModel
self' <- a -> IO (Ptr ShortcutModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr ShortcutManager
manager' <- b -> IO (Ptr ShortcutManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
manager
Ptr ShortcutModel -> Ptr ShortcutManager -> IO ()
dzl_shortcut_model_set_manager Ptr ShortcutModel
self' Ptr ShortcutManager
manager'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
manager
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ShortcutModelSetManagerMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsShortcutModel a, Dazzle.ShortcutManager.IsShortcutManager b) => O.OverloadedMethod ShortcutModelSetManagerMethodInfo a signature where
overloadedMethod = shortcutModelSetManager
instance O.OverloadedMethodInfo ShortcutModelSetManagerMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.ShortcutModel.shortcutModelSetManager",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-ShortcutModel.html#v:shortcutModelSetManager"
})
#endif
foreign import ccall "dzl_shortcut_model_set_theme" dzl_shortcut_model_set_theme ::
Ptr ShortcutModel ->
Ptr Dazzle.ShortcutTheme.ShortcutTheme ->
IO ()
shortcutModelSetTheme ::
(B.CallStack.HasCallStack, MonadIO m, IsShortcutModel a, Dazzle.ShortcutTheme.IsShortcutTheme b) =>
a
-> b
-> m ()
shortcutModelSetTheme :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsShortcutModel a, IsShortcutTheme b) =>
a -> b -> m ()
shortcutModelSetTheme a
self b
theme = 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 ShortcutModel
self' <- a -> IO (Ptr ShortcutModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr ShortcutTheme
theme' <- b -> IO (Ptr ShortcutTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
theme
Ptr ShortcutModel -> Ptr ShortcutTheme -> IO ()
dzl_shortcut_model_set_theme Ptr ShortcutModel
self' Ptr ShortcutTheme
theme'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
theme
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ShortcutModelSetThemeMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsShortcutModel a, Dazzle.ShortcutTheme.IsShortcutTheme b) => O.OverloadedMethod ShortcutModelSetThemeMethodInfo a signature where
overloadedMethod = shortcutModelSetTheme
instance O.OverloadedMethodInfo ShortcutModelSetThemeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.ShortcutModel.shortcutModelSetTheme",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-ShortcutModel.html#v:shortcutModelSetTheme"
})
#endif
foreign import ccall "dzl_shortcut_model_new" dzl_shortcut_model_new ::
IO (Ptr Gtk.TreeModel.TreeModel)
shortcutModelNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m Gtk.TreeModel.TreeModel
shortcutModelNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m TreeModel
shortcutModelNew = IO TreeModel -> m TreeModel
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TreeModel -> m TreeModel) -> IO TreeModel -> m TreeModel
forall a b. (a -> b) -> a -> b
$ do
Ptr TreeModel
result <- IO (Ptr TreeModel)
dzl_shortcut_model_new
Text -> Ptr TreeModel -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"shortcutModelNew" Ptr TreeModel
result
TreeModel
result' <- ((ManagedPtr TreeModel -> TreeModel)
-> Ptr TreeModel -> IO TreeModel
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr TreeModel -> TreeModel
Gtk.TreeModel.TreeModel) Ptr TreeModel
result
TreeModel -> IO TreeModel
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TreeModel
result'
#if defined(ENABLE_OVERLOADING)
#endif