{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Dazzle.Objects.DockWidget
(
DockWidget(..) ,
IsDockWidget ,
toDockWidget ,
#if defined(ENABLE_OVERLOADING)
ResolveDockWidgetMethod ,
#endif
dockWidgetNew ,
#if defined(ENABLE_OVERLOADING)
DockWidgetSetGiconMethodInfo ,
#endif
dockWidgetSetGicon ,
#if defined(ENABLE_OVERLOADING)
DockWidgetSetIconNameMethodInfo ,
#endif
dockWidgetSetIconName ,
#if defined(ENABLE_OVERLOADING)
DockWidgetSetTitleMethodInfo ,
#endif
dockWidgetSetTitle ,
#if defined(ENABLE_OVERLOADING)
DockWidgetCanClosePropertyInfo ,
#endif
constructDockWidgetCanClose ,
#if defined(ENABLE_OVERLOADING)
dockWidgetCanClose ,
#endif
getDockWidgetCanClose ,
setDockWidgetCanClose ,
#if defined(ENABLE_OVERLOADING)
DockWidgetGiconPropertyInfo ,
#endif
constructDockWidgetGicon ,
#if defined(ENABLE_OVERLOADING)
dockWidgetGicon ,
#endif
getDockWidgetGicon ,
setDockWidgetGicon ,
#if defined(ENABLE_OVERLOADING)
DockWidgetIconNamePropertyInfo ,
#endif
constructDockWidgetIconName ,
#if defined(ENABLE_OVERLOADING)
dockWidgetIconName ,
#endif
getDockWidgetIconName ,
setDockWidgetIconName ,
#if defined(ENABLE_OVERLOADING)
DockWidgetManagerPropertyInfo ,
#endif
clearDockWidgetManager ,
constructDockWidgetManager ,
#if defined(ENABLE_OVERLOADING)
dockWidgetManager ,
#endif
getDockWidgetManager ,
setDockWidgetManager ,
#if defined(ENABLE_OVERLOADING)
DockWidgetTitlePropertyInfo ,
#endif
constructDockWidgetTitle ,
#if defined(ENABLE_OVERLOADING)
dockWidgetTitle ,
#endif
getDockWidgetTitle ,
setDockWidgetTitle ,
) 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.Interfaces.Dock as Dazzle.Dock
import {-# SOURCE #-} qualified GI.Dazzle.Interfaces.DockItem as Dazzle.DockItem
import {-# SOURCE #-} qualified GI.Dazzle.Objects.Bin as Dazzle.Bin
import {-# SOURCE #-} qualified GI.Dazzle.Objects.DockManager as Dazzle.DockManager
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gtk.Enums as Gtk.Enums
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Objects.Bin as Gtk.Bin
import qualified GI.Gtk.Objects.Container as Gtk.Container
import qualified GI.Gtk.Objects.Widget as Gtk.Widget
#else
import qualified GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import {-# SOURCE #-} qualified GI.Dazzle.Interfaces.DockItem as Dazzle.DockItem
import {-# SOURCE #-} qualified GI.Dazzle.Objects.Bin as Dazzle.Bin
import {-# SOURCE #-} qualified GI.Dazzle.Objects.DockManager as Dazzle.DockManager
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Objects.Bin as Gtk.Bin
import qualified GI.Gtk.Objects.Container as Gtk.Container
import qualified GI.Gtk.Objects.Widget as Gtk.Widget
#endif
newtype DockWidget = DockWidget (SP.ManagedPtr DockWidget)
deriving (DockWidget -> DockWidget -> Bool
(DockWidget -> DockWidget -> Bool)
-> (DockWidget -> DockWidget -> Bool) -> Eq DockWidget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DockWidget -> DockWidget -> Bool
== :: DockWidget -> DockWidget -> Bool
$c/= :: DockWidget -> DockWidget -> Bool
/= :: DockWidget -> DockWidget -> Bool
Eq)
instance SP.ManagedPtrNewtype DockWidget where
toManagedPtr :: DockWidget -> ManagedPtr DockWidget
toManagedPtr (DockWidget ManagedPtr DockWidget
p) = ManagedPtr DockWidget
p
foreign import ccall "dzl_dock_widget_get_type"
c_dzl_dock_widget_get_type :: IO B.Types.GType
instance B.Types.TypedObject DockWidget where
glibType :: IO GType
glibType = IO GType
c_dzl_dock_widget_get_type
instance B.Types.GObject DockWidget
class (SP.GObject o, O.IsDescendantOf DockWidget o) => IsDockWidget o
instance (SP.GObject o, O.IsDescendantOf DockWidget o) => IsDockWidget o
instance O.HasParentTypes DockWidget
type instance O.ParentTypes DockWidget = '[Dazzle.Bin.Bin, Gtk.Bin.Bin, Gtk.Container.Container, Gtk.Widget.Widget, GObject.Object.Object, Atk.ImplementorIface.ImplementorIface, Dazzle.DockItem.DockItem, Gtk.Buildable.Buildable]
toDockWidget :: (MIO.MonadIO m, IsDockWidget o) => o -> m DockWidget
toDockWidget :: forall (m :: * -> *) o.
(MonadIO m, IsDockWidget o) =>
o -> m DockWidget
toDockWidget = IO DockWidget -> m DockWidget
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO DockWidget -> m DockWidget)
-> (o -> IO DockWidget) -> o -> m DockWidget
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DockWidget -> DockWidget) -> o -> IO DockWidget
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr DockWidget -> DockWidget
DockWidget
instance B.GValue.IsGValue (Maybe DockWidget) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_dzl_dock_widget_get_type
gvalueSet_ :: Ptr GValue -> Maybe DockWidget -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DockWidget
P.Nothing = Ptr GValue -> Ptr DockWidget -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DockWidget
forall a. Ptr a
FP.nullPtr :: FP.Ptr DockWidget)
gvalueSet_ Ptr GValue
gv (P.Just DockWidget
obj) = DockWidget -> (Ptr DockWidget -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DockWidget
obj (Ptr GValue -> Ptr DockWidget -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe DockWidget)
gvalueGet_ Ptr GValue
gv = do
Ptr DockWidget
ptr <- Ptr GValue -> IO (Ptr DockWidget)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DockWidget)
if Ptr DockWidget
ptr Ptr DockWidget -> Ptr DockWidget -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DockWidget
forall a. Ptr a
FP.nullPtr
then DockWidget -> Maybe DockWidget
forall a. a -> Maybe a
P.Just (DockWidget -> Maybe DockWidget)
-> IO DockWidget -> IO (Maybe DockWidget)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr DockWidget -> DockWidget)
-> Ptr DockWidget -> IO DockWidget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DockWidget -> DockWidget
DockWidget Ptr DockWidget
ptr
else Maybe DockWidget -> IO (Maybe DockWidget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DockWidget
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveDockWidgetMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveDockWidgetMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
ResolveDockWidgetMethod "add" o = Gtk.Container.ContainerAddMethodInfo
ResolveDockWidgetMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
ResolveDockWidgetMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
ResolveDockWidgetMethod "addDeviceEvents" o = Gtk.Widget.WidgetAddDeviceEventsMethodInfo
ResolveDockWidgetMethod "addEvents" o = Gtk.Widget.WidgetAddEventsMethodInfo
ResolveDockWidgetMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
ResolveDockWidgetMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
ResolveDockWidgetMethod "adopt" o = Dazzle.DockItem.DockItemAdoptMethodInfo
ResolveDockWidgetMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveDockWidgetMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveDockWidgetMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
ResolveDockWidgetMethod "checkResize" o = Gtk.Container.ContainerCheckResizeMethodInfo
ResolveDockWidgetMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
ResolveDockWidgetMethod "childGetProperty" o = Gtk.Container.ContainerChildGetPropertyMethodInfo
ResolveDockWidgetMethod "childNotify" o = Gtk.Container.ContainerChildNotifyMethodInfo
ResolveDockWidgetMethod "childNotifyByPspec" o = Gtk.Container.ContainerChildNotifyByPspecMethodInfo
ResolveDockWidgetMethod "childSetProperty" o = Gtk.Container.ContainerChildSetPropertyMethodInfo
ResolveDockWidgetMethod "childType" o = Gtk.Container.ContainerChildTypeMethodInfo
ResolveDockWidgetMethod "classPath" o = Gtk.Widget.WidgetClassPathMethodInfo
ResolveDockWidgetMethod "close" o = Dazzle.DockItem.DockItemCloseMethodInfo
ResolveDockWidgetMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
ResolveDockWidgetMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
ResolveDockWidgetMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
ResolveDockWidgetMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
ResolveDockWidgetMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
ResolveDockWidgetMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
ResolveDockWidgetMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
ResolveDockWidgetMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
ResolveDockWidgetMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
ResolveDockWidgetMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
ResolveDockWidgetMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
ResolveDockWidgetMethod "dragBeginWithCoordinates" o = Gtk.Widget.WidgetDragBeginWithCoordinatesMethodInfo
ResolveDockWidgetMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
ResolveDockWidgetMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
ResolveDockWidgetMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
ResolveDockWidgetMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
ResolveDockWidgetMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
ResolveDockWidgetMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
ResolveDockWidgetMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
ResolveDockWidgetMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
ResolveDockWidgetMethod "dragDestSetProxy" o = Gtk.Widget.WidgetDragDestSetProxyMethodInfo
ResolveDockWidgetMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
ResolveDockWidgetMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
ResolveDockWidgetMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
ResolveDockWidgetMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
ResolveDockWidgetMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
ResolveDockWidgetMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
ResolveDockWidgetMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
ResolveDockWidgetMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
ResolveDockWidgetMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
ResolveDockWidgetMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
ResolveDockWidgetMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
ResolveDockWidgetMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
ResolveDockWidgetMethod "dragSourceSetIconPixbuf" o = Gtk.Widget.WidgetDragSourceSetIconPixbufMethodInfo
ResolveDockWidgetMethod "dragSourceSetIconStock" o = Gtk.Widget.WidgetDragSourceSetIconStockMethodInfo
ResolveDockWidgetMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
ResolveDockWidgetMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
ResolveDockWidgetMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
ResolveDockWidgetMethod "draw" o = Gtk.Widget.WidgetDrawMethodInfo
ResolveDockWidgetMethod "emitPresented" o = Dazzle.DockItem.DockItemEmitPresentedMethodInfo
ResolveDockWidgetMethod "ensureStyle" o = Gtk.Widget.WidgetEnsureStyleMethodInfo
ResolveDockWidgetMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
ResolveDockWidgetMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
ResolveDockWidgetMethod "forall" o = Gtk.Container.ContainerForallMethodInfo
ResolveDockWidgetMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveDockWidgetMethod "foreach" o = Gtk.Container.ContainerForeachMethodInfo
ResolveDockWidgetMethod "freezeChildNotify" o = Gtk.Widget.WidgetFreezeChildNotifyMethodInfo
ResolveDockWidgetMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveDockWidgetMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveDockWidgetMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
ResolveDockWidgetMethod "grabDefault" o = Gtk.Widget.WidgetGrabDefaultMethodInfo
ResolveDockWidgetMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
ResolveDockWidgetMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
ResolveDockWidgetMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
ResolveDockWidgetMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
ResolveDockWidgetMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
ResolveDockWidgetMethod "hasRcStyle" o = Gtk.Widget.WidgetHasRcStyleMethodInfo
ResolveDockWidgetMethod "hasScreen" o = Gtk.Widget.WidgetHasScreenMethodInfo
ResolveDockWidgetMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
ResolveDockWidgetMethod "hasWidgets" o = Dazzle.DockItem.DockItemHasWidgetsMethodInfo
ResolveDockWidgetMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
ResolveDockWidgetMethod "hideOnDelete" o = Gtk.Widget.WidgetHideOnDeleteMethodInfo
ResolveDockWidgetMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
ResolveDockWidgetMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
ResolveDockWidgetMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
ResolveDockWidgetMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
ResolveDockWidgetMethod "intersect" o = Gtk.Widget.WidgetIntersectMethodInfo
ResolveDockWidgetMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
ResolveDockWidgetMethod "isComposited" o = Gtk.Widget.WidgetIsCompositedMethodInfo
ResolveDockWidgetMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
ResolveDockWidgetMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveDockWidgetMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
ResolveDockWidgetMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
ResolveDockWidgetMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
ResolveDockWidgetMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
ResolveDockWidgetMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
ResolveDockWidgetMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
ResolveDockWidgetMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
ResolveDockWidgetMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
ResolveDockWidgetMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
ResolveDockWidgetMethod "minimize" o = Dazzle.DockItem.DockItemMinimizeMethodInfo
ResolveDockWidgetMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
ResolveDockWidgetMethod "modifyBase" o = Gtk.Widget.WidgetModifyBaseMethodInfo
ResolveDockWidgetMethod "modifyBg" o = Gtk.Widget.WidgetModifyBgMethodInfo
ResolveDockWidgetMethod "modifyCursor" o = Gtk.Widget.WidgetModifyCursorMethodInfo
ResolveDockWidgetMethod "modifyFg" o = Gtk.Widget.WidgetModifyFgMethodInfo
ResolveDockWidgetMethod "modifyFont" o = Gtk.Widget.WidgetModifyFontMethodInfo
ResolveDockWidgetMethod "modifyStyle" o = Gtk.Widget.WidgetModifyStyleMethodInfo
ResolveDockWidgetMethod "modifyText" o = Gtk.Widget.WidgetModifyTextMethodInfo
ResolveDockWidgetMethod "needsAttention" o = Dazzle.DockItem.DockItemNeedsAttentionMethodInfo
ResolveDockWidgetMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveDockWidgetMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveDockWidgetMethod "overrideBackgroundColor" o = Gtk.Widget.WidgetOverrideBackgroundColorMethodInfo
ResolveDockWidgetMethod "overrideColor" o = Gtk.Widget.WidgetOverrideColorMethodInfo
ResolveDockWidgetMethod "overrideCursor" o = Gtk.Widget.WidgetOverrideCursorMethodInfo
ResolveDockWidgetMethod "overrideFont" o = Gtk.Widget.WidgetOverrideFontMethodInfo
ResolveDockWidgetMethod "overrideSymbolicColor" o = Gtk.Widget.WidgetOverrideSymbolicColorMethodInfo
ResolveDockWidgetMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
ResolveDockWidgetMethod "path" o = Gtk.Widget.WidgetPathMethodInfo
ResolveDockWidgetMethod "present" o = Dazzle.DockItem.DockItemPresentMethodInfo
ResolveDockWidgetMethod "presentChild" o = Dazzle.DockItem.DockItemPresentChildMethodInfo
ResolveDockWidgetMethod "propagateDraw" o = Gtk.Container.ContainerPropagateDrawMethodInfo
ResolveDockWidgetMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
ResolveDockWidgetMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
ResolveDockWidgetMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
ResolveDockWidgetMethod "queueDrawArea" o = Gtk.Widget.WidgetQueueDrawAreaMethodInfo
ResolveDockWidgetMethod "queueDrawRegion" o = Gtk.Widget.WidgetQueueDrawRegionMethodInfo
ResolveDockWidgetMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
ResolveDockWidgetMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
ResolveDockWidgetMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
ResolveDockWidgetMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveDockWidgetMethod "refGicon" o = Dazzle.DockItem.DockItemRefGiconMethodInfo
ResolveDockWidgetMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveDockWidgetMethod "regionIntersect" o = Gtk.Widget.WidgetRegionIntersectMethodInfo
ResolveDockWidgetMethod "registerWindow" o = Gtk.Widget.WidgetRegisterWindowMethodInfo
ResolveDockWidgetMethod "release" o = Dazzle.DockItem.DockItemReleaseMethodInfo
ResolveDockWidgetMethod "remove" o = Gtk.Container.ContainerRemoveMethodInfo
ResolveDockWidgetMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
ResolveDockWidgetMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
ResolveDockWidgetMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
ResolveDockWidgetMethod "renderIcon" o = Gtk.Widget.WidgetRenderIconMethodInfo
ResolveDockWidgetMethod "renderIconPixbuf" o = Gtk.Widget.WidgetRenderIconPixbufMethodInfo
ResolveDockWidgetMethod "reparent" o = Gtk.Widget.WidgetReparentMethodInfo
ResolveDockWidgetMethod "resetRcStyles" o = Gtk.Widget.WidgetResetRcStylesMethodInfo
ResolveDockWidgetMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
ResolveDockWidgetMethod "resizeChildren" o = Gtk.Container.ContainerResizeChildrenMethodInfo
ResolveDockWidgetMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveDockWidgetMethod "sendExpose" o = Gtk.Widget.WidgetSendExposeMethodInfo
ResolveDockWidgetMethod "sendFocusChange" o = Gtk.Widget.WidgetSendFocusChangeMethodInfo
ResolveDockWidgetMethod "shapeCombineRegion" o = Gtk.Widget.WidgetShapeCombineRegionMethodInfo
ResolveDockWidgetMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
ResolveDockWidgetMethod "showAll" o = Gtk.Widget.WidgetShowAllMethodInfo
ResolveDockWidgetMethod "showNow" o = Gtk.Widget.WidgetShowNowMethodInfo
ResolveDockWidgetMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
ResolveDockWidgetMethod "sizeAllocateWithBaseline" o = Gtk.Widget.WidgetSizeAllocateWithBaselineMethodInfo
ResolveDockWidgetMethod "sizeRequest" o = Gtk.Widget.WidgetSizeRequestMethodInfo
ResolveDockWidgetMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveDockWidgetMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveDockWidgetMethod "styleAttach" o = Gtk.Widget.WidgetStyleAttachMethodInfo
ResolveDockWidgetMethod "styleGetProperty" o = Gtk.Widget.WidgetStyleGetPropertyMethodInfo
ResolveDockWidgetMethod "thawChildNotify" o = Gtk.Widget.WidgetThawChildNotifyMethodInfo
ResolveDockWidgetMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveDockWidgetMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
ResolveDockWidgetMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
ResolveDockWidgetMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
ResolveDockWidgetMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
ResolveDockWidgetMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
ResolveDockWidgetMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveDockWidgetMethod "unregisterWindow" o = Gtk.Widget.WidgetUnregisterWindowMethodInfo
ResolveDockWidgetMethod "unsetFocusChain" o = Gtk.Container.ContainerUnsetFocusChainMethodInfo
ResolveDockWidgetMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
ResolveDockWidgetMethod "updateVisibility" o = Dazzle.DockItem.DockItemUpdateVisibilityMethodInfo
ResolveDockWidgetMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveDockWidgetMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
ResolveDockWidgetMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
ResolveDockWidgetMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
ResolveDockWidgetMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
ResolveDockWidgetMethod "getAllocatedSize" o = Gtk.Widget.WidgetGetAllocatedSizeMethodInfo
ResolveDockWidgetMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
ResolveDockWidgetMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
ResolveDockWidgetMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
ResolveDockWidgetMethod "getAppPaintable" o = Gtk.Widget.WidgetGetAppPaintableMethodInfo
ResolveDockWidgetMethod "getBorderWidth" o = Gtk.Container.ContainerGetBorderWidthMethodInfo
ResolveDockWidgetMethod "getCanClose" o = Dazzle.DockItem.DockItemGetCanCloseMethodInfo
ResolveDockWidgetMethod "getCanDefault" o = Gtk.Widget.WidgetGetCanDefaultMethodInfo
ResolveDockWidgetMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
ResolveDockWidgetMethod "getCanMinimize" o = Dazzle.DockItem.DockItemGetCanMinimizeMethodInfo
ResolveDockWidgetMethod "getChild" o = Gtk.Bin.BinGetChildMethodInfo
ResolveDockWidgetMethod "getChildRequisition" o = Gtk.Widget.WidgetGetChildRequisitionMethodInfo
ResolveDockWidgetMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
ResolveDockWidgetMethod "getChildren" o = Gtk.Container.ContainerGetChildrenMethodInfo
ResolveDockWidgetMethod "getClip" o = Gtk.Widget.WidgetGetClipMethodInfo
ResolveDockWidgetMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
ResolveDockWidgetMethod "getCompositeName" o = Gtk.Widget.WidgetGetCompositeNameMethodInfo
ResolveDockWidgetMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveDockWidgetMethod "getDeviceEnabled" o = Gtk.Widget.WidgetGetDeviceEnabledMethodInfo
ResolveDockWidgetMethod "getDeviceEvents" o = Gtk.Widget.WidgetGetDeviceEventsMethodInfo
ResolveDockWidgetMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
ResolveDockWidgetMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
ResolveDockWidgetMethod "getDoubleBuffered" o = Gtk.Widget.WidgetGetDoubleBufferedMethodInfo
ResolveDockWidgetMethod "getEvents" o = Gtk.Widget.WidgetGetEventsMethodInfo
ResolveDockWidgetMethod "getFocusChain" o = Gtk.Container.ContainerGetFocusChainMethodInfo
ResolveDockWidgetMethod "getFocusChild" o = Gtk.Container.ContainerGetFocusChildMethodInfo
ResolveDockWidgetMethod "getFocusHadjustment" o = Gtk.Container.ContainerGetFocusHadjustmentMethodInfo
ResolveDockWidgetMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
ResolveDockWidgetMethod "getFocusVadjustment" o = Gtk.Container.ContainerGetFocusVadjustmentMethodInfo
ResolveDockWidgetMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
ResolveDockWidgetMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
ResolveDockWidgetMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
ResolveDockWidgetMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
ResolveDockWidgetMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
ResolveDockWidgetMethod "getHasWindow" o = Gtk.Widget.WidgetGetHasWindowMethodInfo
ResolveDockWidgetMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
ResolveDockWidgetMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
ResolveDockWidgetMethod "getIconName" o = Dazzle.DockItem.DockItemGetIconNameMethodInfo
ResolveDockWidgetMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
ResolveDockWidgetMethod "getManager" o = Dazzle.DockItem.DockItemGetManagerMethodInfo
ResolveDockWidgetMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
ResolveDockWidgetMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
ResolveDockWidgetMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
ResolveDockWidgetMethod "getMarginLeft" o = Gtk.Widget.WidgetGetMarginLeftMethodInfo
ResolveDockWidgetMethod "getMarginRight" o = Gtk.Widget.WidgetGetMarginRightMethodInfo
ResolveDockWidgetMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
ResolveDockWidgetMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
ResolveDockWidgetMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
ResolveDockWidgetMethod "getModifierStyle" o = Gtk.Widget.WidgetGetModifierStyleMethodInfo
ResolveDockWidgetMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
ResolveDockWidgetMethod "getNoShowAll" o = Gtk.Widget.WidgetGetNoShowAllMethodInfo
ResolveDockWidgetMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
ResolveDockWidgetMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
ResolveDockWidgetMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
ResolveDockWidgetMethod "getParentWindow" o = Gtk.Widget.WidgetGetParentWindowMethodInfo
ResolveDockWidgetMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
ResolveDockWidgetMethod "getPathForChild" o = Gtk.Container.ContainerGetPathForChildMethodInfo
ResolveDockWidgetMethod "getPointer" o = Gtk.Widget.WidgetGetPointerMethodInfo
ResolveDockWidgetMethod "getPreferredHeight" o = Gtk.Widget.WidgetGetPreferredHeightMethodInfo
ResolveDockWidgetMethod "getPreferredHeightAndBaselineForWidth" o = Gtk.Widget.WidgetGetPreferredHeightAndBaselineForWidthMethodInfo
ResolveDockWidgetMethod "getPreferredHeightForWidth" o = Gtk.Widget.WidgetGetPreferredHeightForWidthMethodInfo
ResolveDockWidgetMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
ResolveDockWidgetMethod "getPreferredWidth" o = Gtk.Widget.WidgetGetPreferredWidthMethodInfo
ResolveDockWidgetMethod "getPreferredWidthForHeight" o = Gtk.Widget.WidgetGetPreferredWidthForHeightMethodInfo
ResolveDockWidgetMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveDockWidgetMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveDockWidgetMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
ResolveDockWidgetMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
ResolveDockWidgetMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
ResolveDockWidgetMethod "getRequisition" o = Gtk.Widget.WidgetGetRequisitionMethodInfo
ResolveDockWidgetMethod "getResizeMode" o = Gtk.Container.ContainerGetResizeModeMethodInfo
ResolveDockWidgetMethod "getRootWindow" o = Gtk.Widget.WidgetGetRootWindowMethodInfo
ResolveDockWidgetMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
ResolveDockWidgetMethod "getScreen" o = Gtk.Widget.WidgetGetScreenMethodInfo
ResolveDockWidgetMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
ResolveDockWidgetMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
ResolveDockWidgetMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
ResolveDockWidgetMethod "getState" o = Gtk.Widget.WidgetGetStateMethodInfo
ResolveDockWidgetMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
ResolveDockWidgetMethod "getStyle" o = Gtk.Widget.WidgetGetStyleMethodInfo
ResolveDockWidgetMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
ResolveDockWidgetMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
ResolveDockWidgetMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
ResolveDockWidgetMethod "getTitle" o = Dazzle.DockItem.DockItemGetTitleMethodInfo
ResolveDockWidgetMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
ResolveDockWidgetMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
ResolveDockWidgetMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
ResolveDockWidgetMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
ResolveDockWidgetMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
ResolveDockWidgetMethod "getValignWithBaseline" o = Gtk.Widget.WidgetGetValignWithBaselineMethodInfo
ResolveDockWidgetMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
ResolveDockWidgetMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
ResolveDockWidgetMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
ResolveDockWidgetMethod "getVisual" o = Gtk.Widget.WidgetGetVisualMethodInfo
ResolveDockWidgetMethod "getWindow" o = Gtk.Widget.WidgetGetWindowMethodInfo
ResolveDockWidgetMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
ResolveDockWidgetMethod "setAllocation" o = Gtk.Widget.WidgetSetAllocationMethodInfo
ResolveDockWidgetMethod "setAppPaintable" o = Gtk.Widget.WidgetSetAppPaintableMethodInfo
ResolveDockWidgetMethod "setBorderWidth" o = Gtk.Container.ContainerSetBorderWidthMethodInfo
ResolveDockWidgetMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
ResolveDockWidgetMethod "setCanDefault" o = Gtk.Widget.WidgetSetCanDefaultMethodInfo
ResolveDockWidgetMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
ResolveDockWidgetMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
ResolveDockWidgetMethod "setClip" o = Gtk.Widget.WidgetSetClipMethodInfo
ResolveDockWidgetMethod "setCompositeName" o = Gtk.Widget.WidgetSetCompositeNameMethodInfo
ResolveDockWidgetMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveDockWidgetMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveDockWidgetMethod "setDeviceEnabled" o = Gtk.Widget.WidgetSetDeviceEnabledMethodInfo
ResolveDockWidgetMethod "setDeviceEvents" o = Gtk.Widget.WidgetSetDeviceEventsMethodInfo
ResolveDockWidgetMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
ResolveDockWidgetMethod "setDoubleBuffered" o = Gtk.Widget.WidgetSetDoubleBufferedMethodInfo
ResolveDockWidgetMethod "setEvents" o = Gtk.Widget.WidgetSetEventsMethodInfo
ResolveDockWidgetMethod "setFocusChain" o = Gtk.Container.ContainerSetFocusChainMethodInfo
ResolveDockWidgetMethod "setFocusChild" o = Gtk.Container.ContainerSetFocusChildMethodInfo
ResolveDockWidgetMethod "setFocusHadjustment" o = Gtk.Container.ContainerSetFocusHadjustmentMethodInfo
ResolveDockWidgetMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
ResolveDockWidgetMethod "setFocusVadjustment" o = Gtk.Container.ContainerSetFocusVadjustmentMethodInfo
ResolveDockWidgetMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
ResolveDockWidgetMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
ResolveDockWidgetMethod "setGicon" o = DockWidgetSetGiconMethodInfo
ResolveDockWidgetMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
ResolveDockWidgetMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
ResolveDockWidgetMethod "setHasWindow" o = Gtk.Widget.WidgetSetHasWindowMethodInfo
ResolveDockWidgetMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
ResolveDockWidgetMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
ResolveDockWidgetMethod "setIconName" o = DockWidgetSetIconNameMethodInfo
ResolveDockWidgetMethod "setManager" o = Dazzle.DockItem.DockItemSetManagerMethodInfo
ResolveDockWidgetMethod "setMapped" o = Gtk.Widget.WidgetSetMappedMethodInfo
ResolveDockWidgetMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
ResolveDockWidgetMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
ResolveDockWidgetMethod "setMarginLeft" o = Gtk.Widget.WidgetSetMarginLeftMethodInfo
ResolveDockWidgetMethod "setMarginRight" o = Gtk.Widget.WidgetSetMarginRightMethodInfo
ResolveDockWidgetMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
ResolveDockWidgetMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
ResolveDockWidgetMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
ResolveDockWidgetMethod "setNoShowAll" o = Gtk.Widget.WidgetSetNoShowAllMethodInfo
ResolveDockWidgetMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
ResolveDockWidgetMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
ResolveDockWidgetMethod "setParentWindow" o = Gtk.Widget.WidgetSetParentWindowMethodInfo
ResolveDockWidgetMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveDockWidgetMethod "setRealized" o = Gtk.Widget.WidgetSetRealizedMethodInfo
ResolveDockWidgetMethod "setReallocateRedraws" o = Gtk.Container.ContainerSetReallocateRedrawsMethodInfo
ResolveDockWidgetMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
ResolveDockWidgetMethod "setRedrawOnAllocate" o = Gtk.Widget.WidgetSetRedrawOnAllocateMethodInfo
ResolveDockWidgetMethod "setResizeMode" o = Gtk.Container.ContainerSetResizeModeMethodInfo
ResolveDockWidgetMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
ResolveDockWidgetMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
ResolveDockWidgetMethod "setState" o = Gtk.Widget.WidgetSetStateMethodInfo
ResolveDockWidgetMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
ResolveDockWidgetMethod "setStyle" o = Gtk.Widget.WidgetSetStyleMethodInfo
ResolveDockWidgetMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
ResolveDockWidgetMethod "setTitle" o = DockWidgetSetTitleMethodInfo
ResolveDockWidgetMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
ResolveDockWidgetMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
ResolveDockWidgetMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
ResolveDockWidgetMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
ResolveDockWidgetMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
ResolveDockWidgetMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
ResolveDockWidgetMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
ResolveDockWidgetMethod "setVisual" o = Gtk.Widget.WidgetSetVisualMethodInfo
ResolveDockWidgetMethod "setWindow" o = Gtk.Widget.WidgetSetWindowMethodInfo
ResolveDockWidgetMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveDockWidgetMethod t DockWidget, O.OverloadedMethod info DockWidget p) => OL.IsLabel t (DockWidget -> 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 ~ ResolveDockWidgetMethod t DockWidget, O.OverloadedMethod info DockWidget p, R.HasField t DockWidget p) => R.HasField t DockWidget p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveDockWidgetMethod t DockWidget, O.OverloadedMethodInfo info DockWidget) => OL.IsLabel t (O.MethodProxy info DockWidget) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
getDockWidgetCanClose :: (MonadIO m, IsDockWidget o) => o -> m Bool
getDockWidgetCanClose :: forall (m :: * -> *) o. (MonadIO m, IsDockWidget o) => o -> m Bool
getDockWidgetCanClose o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"can-close"
setDockWidgetCanClose :: (MonadIO m, IsDockWidget o) => o -> Bool -> m ()
setDockWidgetCanClose :: forall (m :: * -> *) o.
(MonadIO m, IsDockWidget o) =>
o -> Bool -> m ()
setDockWidgetCanClose o
obj Bool
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 -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"can-close" Bool
val
constructDockWidgetCanClose :: (IsDockWidget o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructDockWidgetCanClose :: forall o (m :: * -> *).
(IsDockWidget o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructDockWidgetCanClose Bool
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 -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"can-close" Bool
val
#if defined(ENABLE_OVERLOADING)
data DockWidgetCanClosePropertyInfo
instance AttrInfo DockWidgetCanClosePropertyInfo where
type AttrAllowedOps DockWidgetCanClosePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint DockWidgetCanClosePropertyInfo = IsDockWidget
type AttrSetTypeConstraint DockWidgetCanClosePropertyInfo = (~) Bool
type AttrTransferTypeConstraint DockWidgetCanClosePropertyInfo = (~) Bool
type AttrTransferType DockWidgetCanClosePropertyInfo = Bool
type AttrGetType DockWidgetCanClosePropertyInfo = Bool
type AttrLabel DockWidgetCanClosePropertyInfo = "can-close"
type AttrOrigin DockWidgetCanClosePropertyInfo = DockWidget
attrGet = getDockWidgetCanClose
attrSet = setDockWidgetCanClose
attrTransfer _ v = do
return v
attrConstruct = constructDockWidgetCanClose
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockWidget.canClose"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockWidget.html#g:attr:canClose"
})
#endif
getDockWidgetGicon :: (MonadIO m, IsDockWidget o) => o -> m (Maybe Gio.Icon.Icon)
getDockWidgetGicon :: forall (m :: * -> *) o.
(MonadIO m, IsDockWidget o) =>
o -> m (Maybe Icon)
getDockWidgetGicon o
obj = IO (Maybe Icon) -> m (Maybe Icon)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Icon) -> m (Maybe Icon))
-> IO (Maybe Icon) -> m (Maybe Icon)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Icon -> Icon) -> IO (Maybe Icon)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"gicon" ManagedPtr Icon -> Icon
Gio.Icon.Icon
setDockWidgetGicon :: (MonadIO m, IsDockWidget o, Gio.Icon.IsIcon a) => o -> a -> m ()
setDockWidgetGicon :: forall (m :: * -> *) o a.
(MonadIO m, IsDockWidget o, IsIcon a) =>
o -> a -> m ()
setDockWidgetGicon 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
"gicon" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructDockWidgetGicon :: (IsDockWidget o, MIO.MonadIO m, Gio.Icon.IsIcon a) => a -> m (GValueConstruct o)
constructDockWidgetGicon :: forall o (m :: * -> *) a.
(IsDockWidget o, MonadIO m, IsIcon a) =>
a -> m (GValueConstruct o)
constructDockWidgetGicon 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
"gicon" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data DockWidgetGiconPropertyInfo
instance AttrInfo DockWidgetGiconPropertyInfo where
type AttrAllowedOps DockWidgetGiconPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint DockWidgetGiconPropertyInfo = IsDockWidget
type AttrSetTypeConstraint DockWidgetGiconPropertyInfo = Gio.Icon.IsIcon
type AttrTransferTypeConstraint DockWidgetGiconPropertyInfo = Gio.Icon.IsIcon
type AttrTransferType DockWidgetGiconPropertyInfo = Gio.Icon.Icon
type AttrGetType DockWidgetGiconPropertyInfo = (Maybe Gio.Icon.Icon)
type AttrLabel DockWidgetGiconPropertyInfo = "gicon"
type AttrOrigin DockWidgetGiconPropertyInfo = DockWidget
attrGet = getDockWidgetGicon
attrSet = setDockWidgetGicon
attrTransfer _ v = do
unsafeCastTo Gio.Icon.Icon v
attrConstruct = constructDockWidgetGicon
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockWidget.gicon"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockWidget.html#g:attr:gicon"
})
#endif
getDockWidgetIconName :: (MonadIO m, IsDockWidget o) => o -> m (Maybe T.Text)
getDockWidgetIconName :: forall (m :: * -> *) o.
(MonadIO m, IsDockWidget o) =>
o -> m (Maybe Text)
getDockWidgetIconName o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"icon-name"
setDockWidgetIconName :: (MonadIO m, IsDockWidget o) => o -> T.Text -> m ()
setDockWidgetIconName :: forall (m :: * -> *) o.
(MonadIO m, IsDockWidget o) =>
o -> Text -> m ()
setDockWidgetIconName o
obj Text
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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"icon-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructDockWidgetIconName :: (IsDockWidget o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructDockWidgetIconName :: forall o (m :: * -> *).
(IsDockWidget o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructDockWidgetIconName Text
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 Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"icon-name" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data DockWidgetIconNamePropertyInfo
instance AttrInfo DockWidgetIconNamePropertyInfo where
type AttrAllowedOps DockWidgetIconNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint DockWidgetIconNamePropertyInfo = IsDockWidget
type AttrSetTypeConstraint DockWidgetIconNamePropertyInfo = (~) T.Text
type AttrTransferTypeConstraint DockWidgetIconNamePropertyInfo = (~) T.Text
type AttrTransferType DockWidgetIconNamePropertyInfo = T.Text
type AttrGetType DockWidgetIconNamePropertyInfo = (Maybe T.Text)
type AttrLabel DockWidgetIconNamePropertyInfo = "icon-name"
type AttrOrigin DockWidgetIconNamePropertyInfo = DockWidget
attrGet = getDockWidgetIconName
attrSet = setDockWidgetIconName
attrTransfer _ v = do
return v
attrConstruct = constructDockWidgetIconName
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockWidget.iconName"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockWidget.html#g:attr:iconName"
})
#endif
getDockWidgetManager :: (MonadIO m, IsDockWidget o) => o -> m (Maybe Dazzle.DockManager.DockManager)
getDockWidgetManager :: forall (m :: * -> *) o.
(MonadIO m, IsDockWidget o) =>
o -> m (Maybe DockManager)
getDockWidgetManager o
obj = IO (Maybe DockManager) -> m (Maybe DockManager)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe DockManager) -> m (Maybe DockManager))
-> IO (Maybe DockManager) -> m (Maybe DockManager)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr DockManager -> DockManager)
-> IO (Maybe DockManager)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"manager" ManagedPtr DockManager -> DockManager
Dazzle.DockManager.DockManager
setDockWidgetManager :: (MonadIO m, IsDockWidget o, Dazzle.DockManager.IsDockManager a) => o -> a -> m ()
setDockWidgetManager :: forall (m :: * -> *) o a.
(MonadIO m, IsDockWidget o, IsDockManager a) =>
o -> a -> m ()
setDockWidgetManager 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)
constructDockWidgetManager :: (IsDockWidget o, MIO.MonadIO m, Dazzle.DockManager.IsDockManager a) => a -> m (GValueConstruct o)
constructDockWidgetManager :: forall o (m :: * -> *) a.
(IsDockWidget o, MonadIO m, IsDockManager a) =>
a -> m (GValueConstruct o)
constructDockWidgetManager 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)
clearDockWidgetManager :: (MonadIO m, IsDockWidget o) => o -> m ()
clearDockWidgetManager :: forall (m :: * -> *) o. (MonadIO m, IsDockWidget o) => o -> m ()
clearDockWidgetManager o
obj = 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
$ o -> String -> Maybe DockManager -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"manager" (Maybe DockManager
forall a. Maybe a
Nothing :: Maybe Dazzle.DockManager.DockManager)
#if defined(ENABLE_OVERLOADING)
data DockWidgetManagerPropertyInfo
instance AttrInfo DockWidgetManagerPropertyInfo where
type AttrAllowedOps DockWidgetManagerPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DockWidgetManagerPropertyInfo = IsDockWidget
type AttrSetTypeConstraint DockWidgetManagerPropertyInfo = Dazzle.DockManager.IsDockManager
type AttrTransferTypeConstraint DockWidgetManagerPropertyInfo = Dazzle.DockManager.IsDockManager
type AttrTransferType DockWidgetManagerPropertyInfo = Dazzle.DockManager.DockManager
type AttrGetType DockWidgetManagerPropertyInfo = (Maybe Dazzle.DockManager.DockManager)
type AttrLabel DockWidgetManagerPropertyInfo = "manager"
type AttrOrigin DockWidgetManagerPropertyInfo = DockWidget
attrGet = getDockWidgetManager
attrSet = setDockWidgetManager
attrTransfer _ v = do
unsafeCastTo Dazzle.DockManager.DockManager v
attrConstruct = constructDockWidgetManager
attrClear = clearDockWidgetManager
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockWidget.manager"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockWidget.html#g:attr:manager"
})
#endif
getDockWidgetTitle :: (MonadIO m, IsDockWidget o) => o -> m (Maybe T.Text)
getDockWidgetTitle :: forall (m :: * -> *) o.
(MonadIO m, IsDockWidget o) =>
o -> m (Maybe Text)
getDockWidgetTitle o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"title"
setDockWidgetTitle :: (MonadIO m, IsDockWidget o) => o -> T.Text -> m ()
setDockWidgetTitle :: forall (m :: * -> *) o.
(MonadIO m, IsDockWidget o) =>
o -> Text -> m ()
setDockWidgetTitle o
obj Text
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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"title" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructDockWidgetTitle :: (IsDockWidget o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructDockWidgetTitle :: forall o (m :: * -> *).
(IsDockWidget o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructDockWidgetTitle Text
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 Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"title" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data DockWidgetTitlePropertyInfo
instance AttrInfo DockWidgetTitlePropertyInfo where
type AttrAllowedOps DockWidgetTitlePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint DockWidgetTitlePropertyInfo = IsDockWidget
type AttrSetTypeConstraint DockWidgetTitlePropertyInfo = (~) T.Text
type AttrTransferTypeConstraint DockWidgetTitlePropertyInfo = (~) T.Text
type AttrTransferType DockWidgetTitlePropertyInfo = T.Text
type AttrGetType DockWidgetTitlePropertyInfo = (Maybe T.Text)
type AttrLabel DockWidgetTitlePropertyInfo = "title"
type AttrOrigin DockWidgetTitlePropertyInfo = DockWidget
attrGet = getDockWidgetTitle
attrSet = setDockWidgetTitle
attrTransfer _ v = do
return v
attrConstruct = constructDockWidgetTitle
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockWidget.title"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockWidget.html#g:attr:title"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DockWidget
type instance O.AttributeList DockWidget = DockWidgetAttributeList
type DockWidgetAttributeList = ('[ '("appPaintable", Gtk.Widget.WidgetAppPaintablePropertyInfo), '("borderWidth", Gtk.Container.ContainerBorderWidthPropertyInfo), '("canClose", DockWidgetCanClosePropertyInfo), '("canDefault", Gtk.Widget.WidgetCanDefaultPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("child", Gtk.Container.ContainerChildPropertyInfo), '("compositeChild", Gtk.Widget.WidgetCompositeChildPropertyInfo), '("doubleBuffered", Gtk.Widget.WidgetDoubleBufferedPropertyInfo), '("events", Gtk.Widget.WidgetEventsPropertyInfo), '("expand", Gtk.Widget.WidgetExpandPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("gicon", DockWidgetGiconPropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("iconName", DockWidgetIconNamePropertyInfo), '("isFocus", Gtk.Widget.WidgetIsFocusPropertyInfo), '("manager", DockWidgetManagerPropertyInfo), '("margin", Gtk.Widget.WidgetMarginPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginLeft", Gtk.Widget.WidgetMarginLeftPropertyInfo), '("marginRight", Gtk.Widget.WidgetMarginRightPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("noShowAll", Gtk.Widget.WidgetNoShowAllPropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("resizeMode", Gtk.Container.ContainerResizeModePropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("style", Gtk.Widget.WidgetStylePropertyInfo), '("title", DockWidgetTitlePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo), '("window", Gtk.Widget.WidgetWindowPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
dockWidgetCanClose :: AttrLabelProxy "canClose"
dockWidgetCanClose = AttrLabelProxy
dockWidgetGicon :: AttrLabelProxy "gicon"
dockWidgetGicon = AttrLabelProxy
dockWidgetIconName :: AttrLabelProxy "iconName"
dockWidgetIconName = AttrLabelProxy
dockWidgetManager :: AttrLabelProxy "manager"
dockWidgetManager = AttrLabelProxy
dockWidgetTitle :: AttrLabelProxy "title"
dockWidgetTitle = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DockWidget = DockWidgetSignalList
type DockWidgetSignalList = ('[ '("accelClosuresChanged", Gtk.Widget.WidgetAccelClosuresChangedSignalInfo), '("add", Gtk.Container.ContainerAddSignalInfo), '("buttonPressEvent", Gtk.Widget.WidgetButtonPressEventSignalInfo), '("buttonReleaseEvent", Gtk.Widget.WidgetButtonReleaseEventSignalInfo), '("canActivateAccel", Gtk.Widget.WidgetCanActivateAccelSignalInfo), '("checkResize", Gtk.Container.ContainerCheckResizeSignalInfo), '("childNotify", Gtk.Widget.WidgetChildNotifySignalInfo), '("compositedChanged", Gtk.Widget.WidgetCompositedChangedSignalInfo), '("configureEvent", Gtk.Widget.WidgetConfigureEventSignalInfo), '("damageEvent", Gtk.Widget.WidgetDamageEventSignalInfo), '("deleteEvent", Gtk.Widget.WidgetDeleteEventSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("destroyEvent", Gtk.Widget.WidgetDestroyEventSignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("dragBegin", Gtk.Widget.WidgetDragBeginSignalInfo), '("dragDataDelete", Gtk.Widget.WidgetDragDataDeleteSignalInfo), '("dragDataGet", Gtk.Widget.WidgetDragDataGetSignalInfo), '("dragDataReceived", Gtk.Widget.WidgetDragDataReceivedSignalInfo), '("dragDrop", Gtk.Widget.WidgetDragDropSignalInfo), '("dragEnd", Gtk.Widget.WidgetDragEndSignalInfo), '("dragFailed", Gtk.Widget.WidgetDragFailedSignalInfo), '("dragLeave", Gtk.Widget.WidgetDragLeaveSignalInfo), '("dragMotion", Gtk.Widget.WidgetDragMotionSignalInfo), '("draw", Gtk.Widget.WidgetDrawSignalInfo), '("enterNotifyEvent", Gtk.Widget.WidgetEnterNotifyEventSignalInfo), '("event", Gtk.Widget.WidgetEventSignalInfo), '("eventAfter", Gtk.Widget.WidgetEventAfterSignalInfo), '("focus", Gtk.Widget.WidgetFocusSignalInfo), '("focusInEvent", Gtk.Widget.WidgetFocusInEventSignalInfo), '("focusOutEvent", Gtk.Widget.WidgetFocusOutEventSignalInfo), '("grabBrokenEvent", Gtk.Widget.WidgetGrabBrokenEventSignalInfo), '("grabFocus", Gtk.Widget.WidgetGrabFocusSignalInfo), '("grabNotify", Gtk.Widget.WidgetGrabNotifySignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("hierarchyChanged", Gtk.Widget.WidgetHierarchyChangedSignalInfo), '("keyPressEvent", Gtk.Widget.WidgetKeyPressEventSignalInfo), '("keyReleaseEvent", Gtk.Widget.WidgetKeyReleaseEventSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("leaveNotifyEvent", Gtk.Widget.WidgetLeaveNotifyEventSignalInfo), '("managerSet", Dazzle.DockItem.DockItemManagerSetSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mapEvent", Gtk.Widget.WidgetMapEventSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("motionNotifyEvent", Gtk.Widget.WidgetMotionNotifyEventSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("needsAttention", Dazzle.DockItem.DockItemNeedsAttentionSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("parentSet", Gtk.Widget.WidgetParentSetSignalInfo), '("popupMenu", Gtk.Widget.WidgetPopupMenuSignalInfo), '("presented", Dazzle.DockItem.DockItemPresentedSignalInfo), '("propertyNotifyEvent", Gtk.Widget.WidgetPropertyNotifyEventSignalInfo), '("proximityInEvent", Gtk.Widget.WidgetProximityInEventSignalInfo), '("proximityOutEvent", Gtk.Widget.WidgetProximityOutEventSignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("remove", Gtk.Container.ContainerRemoveSignalInfo), '("screenChanged", Gtk.Widget.WidgetScreenChangedSignalInfo), '("scrollEvent", Gtk.Widget.WidgetScrollEventSignalInfo), '("selectionClearEvent", Gtk.Widget.WidgetSelectionClearEventSignalInfo), '("selectionGet", Gtk.Widget.WidgetSelectionGetSignalInfo), '("selectionNotifyEvent", Gtk.Widget.WidgetSelectionNotifyEventSignalInfo), '("selectionReceived", Gtk.Widget.WidgetSelectionReceivedSignalInfo), '("selectionRequestEvent", Gtk.Widget.WidgetSelectionRequestEventSignalInfo), '("setFocusChild", Gtk.Container.ContainerSetFocusChildSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("showHelp", Gtk.Widget.WidgetShowHelpSignalInfo), '("sizeAllocate", Gtk.Widget.WidgetSizeAllocateSignalInfo), '("stateChanged", Gtk.Widget.WidgetStateChangedSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("styleSet", Gtk.Widget.WidgetStyleSetSignalInfo), '("styleUpdated", Gtk.Widget.WidgetStyleUpdatedSignalInfo), '("touchEvent", Gtk.Widget.WidgetTouchEventSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unmapEvent", Gtk.Widget.WidgetUnmapEventSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo), '("visibilityNotifyEvent", Gtk.Widget.WidgetVisibilityNotifyEventSignalInfo), '("windowStateEvent", Gtk.Widget.WidgetWindowStateEventSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "dzl_dock_widget_new" dzl_dock_widget_new ::
IO (Ptr DockWidget)
dockWidgetNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m DockWidget
dockWidgetNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m DockWidget
dockWidgetNew = IO DockWidget -> m DockWidget
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DockWidget -> m DockWidget) -> IO DockWidget -> m DockWidget
forall a b. (a -> b) -> a -> b
$ do
Ptr DockWidget
result <- IO (Ptr DockWidget)
dzl_dock_widget_new
Text -> Ptr DockWidget -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dockWidgetNew" Ptr DockWidget
result
DockWidget
result' <- ((ManagedPtr DockWidget -> DockWidget)
-> Ptr DockWidget -> IO DockWidget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DockWidget -> DockWidget
DockWidget) Ptr DockWidget
result
DockWidget -> IO DockWidget
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return DockWidget
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "dzl_dock_widget_set_gicon" dzl_dock_widget_set_gicon ::
Ptr DockWidget ->
Ptr Gio.Icon.Icon ->
IO ()
dockWidgetSetGicon ::
(B.CallStack.HasCallStack, MonadIO m, IsDockWidget a, Gio.Icon.IsIcon b) =>
a
-> b
-> m ()
dockWidgetSetGicon :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDockWidget a, IsIcon b) =>
a -> b -> m ()
dockWidgetSetGicon a
self b
gicon = 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 DockWidget
self' <- a -> IO (Ptr DockWidget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr Icon
gicon' <- b -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
gicon
Ptr DockWidget -> Ptr Icon -> IO ()
dzl_dock_widget_set_gicon Ptr DockWidget
self' Ptr Icon
gicon'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
gicon
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DockWidgetSetGiconMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsDockWidget a, Gio.Icon.IsIcon b) => O.OverloadedMethod DockWidgetSetGiconMethodInfo a signature where
overloadedMethod = dockWidgetSetGicon
instance O.OverloadedMethodInfo DockWidgetSetGiconMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockWidget.dockWidgetSetGicon",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockWidget.html#v:dockWidgetSetGicon"
})
#endif
foreign import ccall "dzl_dock_widget_set_icon_name" dzl_dock_widget_set_icon_name ::
Ptr DockWidget ->
CString ->
IO ()
dockWidgetSetIconName ::
(B.CallStack.HasCallStack, MonadIO m, IsDockWidget a) =>
a
-> T.Text
-> m ()
dockWidgetSetIconName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDockWidget a) =>
a -> Text -> m ()
dockWidgetSetIconName a
self Text
iconName = 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 DockWidget
self' <- a -> IO (Ptr DockWidget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
iconName' <- Text -> IO CString
textToCString Text
iconName
Ptr DockWidget -> CString -> IO ()
dzl_dock_widget_set_icon_name Ptr DockWidget
self' CString
iconName'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconName'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DockWidgetSetIconNameMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDockWidget a) => O.OverloadedMethod DockWidgetSetIconNameMethodInfo a signature where
overloadedMethod = dockWidgetSetIconName
instance O.OverloadedMethodInfo DockWidgetSetIconNameMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockWidget.dockWidgetSetIconName",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockWidget.html#v:dockWidgetSetIconName"
})
#endif
foreign import ccall "dzl_dock_widget_set_title" dzl_dock_widget_set_title ::
Ptr DockWidget ->
CString ->
IO ()
dockWidgetSetTitle ::
(B.CallStack.HasCallStack, MonadIO m, IsDockWidget a) =>
a
-> T.Text
-> m ()
dockWidgetSetTitle :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDockWidget a) =>
a -> Text -> m ()
dockWidgetSetTitle a
self Text
title = 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 DockWidget
self' <- a -> IO (Ptr DockWidget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
title' <- Text -> IO CString
textToCString Text
title
Ptr DockWidget -> CString -> IO ()
dzl_dock_widget_set_title Ptr DockWidget
self' CString
title'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
title'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DockWidgetSetTitleMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDockWidget a) => O.OverloadedMethod DockWidgetSetTitleMethodInfo a signature where
overloadedMethod = dockWidgetSetTitle
instance O.OverloadedMethodInfo DockWidgetSetTitleMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockWidget.dockWidgetSetTitle",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockWidget.html#v:dockWidgetSetTitle"
})
#endif