{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Dazzle.Objects.DockWindow
(
DockWindow(..) ,
IsDockWindow ,
toDockWindow ,
#if defined(ENABLE_OVERLOADING)
ResolveDockWindowMethod ,
#endif
dockWindowNew ,
) 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.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
import qualified GI.Gtk.Objects.Window as Gtk.Window
#else
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 qualified GI.GObject.Objects.Object as GObject.Object
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
import qualified GI.Gtk.Objects.Window as Gtk.Window
#endif
newtype DockWindow = DockWindow (SP.ManagedPtr DockWindow)
deriving (DockWindow -> DockWindow -> Bool
(DockWindow -> DockWindow -> Bool)
-> (DockWindow -> DockWindow -> Bool) -> Eq DockWindow
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DockWindow -> DockWindow -> Bool
== :: DockWindow -> DockWindow -> Bool
$c/= :: DockWindow -> DockWindow -> Bool
/= :: DockWindow -> DockWindow -> Bool
Eq)
instance SP.ManagedPtrNewtype DockWindow where
toManagedPtr :: DockWindow -> ManagedPtr DockWindow
toManagedPtr (DockWindow ManagedPtr DockWindow
p) = ManagedPtr DockWindow
p
foreign import ccall "dzl_dock_window_get_type"
c_dzl_dock_window_get_type :: IO B.Types.GType
instance B.Types.TypedObject DockWindow where
glibType :: IO GType
glibType = IO GType
c_dzl_dock_window_get_type
instance B.Types.GObject DockWindow
class (SP.GObject o, O.IsDescendantOf DockWindow o) => IsDockWindow o
instance (SP.GObject o, O.IsDescendantOf DockWindow o) => IsDockWindow o
instance O.HasParentTypes DockWindow
type instance O.ParentTypes DockWindow = '[Gtk.Window.Window, Gtk.Bin.Bin, Gtk.Container.Container, Gtk.Widget.Widget, GObject.Object.Object, Atk.ImplementorIface.ImplementorIface, Dazzle.Dock.Dock, Dazzle.DockItem.DockItem, Gtk.Buildable.Buildable]
toDockWindow :: (MIO.MonadIO m, IsDockWindow o) => o -> m DockWindow
toDockWindow :: forall (m :: * -> *) o.
(MonadIO m, IsDockWindow o) =>
o -> m DockWindow
toDockWindow = IO DockWindow -> m DockWindow
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO DockWindow -> m DockWindow)
-> (o -> IO DockWindow) -> o -> m DockWindow
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DockWindow -> DockWindow) -> o -> IO DockWindow
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr DockWindow -> DockWindow
DockWindow
instance B.GValue.IsGValue (Maybe DockWindow) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_dzl_dock_window_get_type
gvalueSet_ :: Ptr GValue -> Maybe DockWindow -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DockWindow
P.Nothing = Ptr GValue -> Ptr DockWindow -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DockWindow
forall a. Ptr a
FP.nullPtr :: FP.Ptr DockWindow)
gvalueSet_ Ptr GValue
gv (P.Just DockWindow
obj) = DockWindow -> (Ptr DockWindow -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DockWindow
obj (Ptr GValue -> Ptr DockWindow -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe DockWindow)
gvalueGet_ Ptr GValue
gv = do
Ptr DockWindow
ptr <- Ptr GValue -> IO (Ptr DockWindow)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DockWindow)
if Ptr DockWindow
ptr Ptr DockWindow -> Ptr DockWindow -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DockWindow
forall a. Ptr a
FP.nullPtr
then DockWindow -> Maybe DockWindow
forall a. a -> Maybe a
P.Just (DockWindow -> Maybe DockWindow)
-> IO DockWindow -> IO (Maybe DockWindow)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr DockWindow -> DockWindow)
-> Ptr DockWindow -> IO DockWindow
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DockWindow -> DockWindow
DockWindow Ptr DockWindow
ptr
else Maybe DockWindow -> IO (Maybe DockWindow)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DockWindow
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveDockWindowMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveDockWindowMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
ResolveDockWindowMethod "activateDefault" o = Gtk.Window.WindowActivateDefaultMethodInfo
ResolveDockWindowMethod "activateFocus" o = Gtk.Window.WindowActivateFocusMethodInfo
ResolveDockWindowMethod "activateKey" o = Gtk.Window.WindowActivateKeyMethodInfo
ResolveDockWindowMethod "add" o = Gtk.Container.ContainerAddMethodInfo
ResolveDockWindowMethod "addAccelGroup" o = Gtk.Window.WindowAddAccelGroupMethodInfo
ResolveDockWindowMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
ResolveDockWindowMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
ResolveDockWindowMethod "addDeviceEvents" o = Gtk.Widget.WidgetAddDeviceEventsMethodInfo
ResolveDockWindowMethod "addEvents" o = Gtk.Widget.WidgetAddEventsMethodInfo
ResolveDockWindowMethod "addMnemonic" o = Gtk.Window.WindowAddMnemonicMethodInfo
ResolveDockWindowMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
ResolveDockWindowMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
ResolveDockWindowMethod "adopt" o = Dazzle.DockItem.DockItemAdoptMethodInfo
ResolveDockWindowMethod "beginMoveDrag" o = Gtk.Window.WindowBeginMoveDragMethodInfo
ResolveDockWindowMethod "beginResizeDrag" o = Gtk.Window.WindowBeginResizeDragMethodInfo
ResolveDockWindowMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveDockWindowMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveDockWindowMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
ResolveDockWindowMethod "checkResize" o = Gtk.Container.ContainerCheckResizeMethodInfo
ResolveDockWindowMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
ResolveDockWindowMethod "childGetProperty" o = Gtk.Container.ContainerChildGetPropertyMethodInfo
ResolveDockWindowMethod "childNotify" o = Gtk.Container.ContainerChildNotifyMethodInfo
ResolveDockWindowMethod "childNotifyByPspec" o = Gtk.Container.ContainerChildNotifyByPspecMethodInfo
ResolveDockWindowMethod "childSetProperty" o = Gtk.Container.ContainerChildSetPropertyMethodInfo
ResolveDockWindowMethod "childType" o = Gtk.Container.ContainerChildTypeMethodInfo
ResolveDockWindowMethod "classPath" o = Gtk.Widget.WidgetClassPathMethodInfo
ResolveDockWindowMethod "close" o = Gtk.Window.WindowCloseMethodInfo
ResolveDockWindowMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
ResolveDockWindowMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
ResolveDockWindowMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
ResolveDockWindowMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
ResolveDockWindowMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
ResolveDockWindowMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
ResolveDockWindowMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
ResolveDockWindowMethod "deiconify" o = Gtk.Window.WindowDeiconifyMethodInfo
ResolveDockWindowMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
ResolveDockWindowMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
ResolveDockWindowMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
ResolveDockWindowMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
ResolveDockWindowMethod "dragBeginWithCoordinates" o = Gtk.Widget.WidgetDragBeginWithCoordinatesMethodInfo
ResolveDockWindowMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
ResolveDockWindowMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
ResolveDockWindowMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
ResolveDockWindowMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
ResolveDockWindowMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
ResolveDockWindowMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
ResolveDockWindowMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
ResolveDockWindowMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
ResolveDockWindowMethod "dragDestSetProxy" o = Gtk.Widget.WidgetDragDestSetProxyMethodInfo
ResolveDockWindowMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
ResolveDockWindowMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
ResolveDockWindowMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
ResolveDockWindowMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
ResolveDockWindowMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
ResolveDockWindowMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
ResolveDockWindowMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
ResolveDockWindowMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
ResolveDockWindowMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
ResolveDockWindowMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
ResolveDockWindowMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
ResolveDockWindowMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
ResolveDockWindowMethod "dragSourceSetIconPixbuf" o = Gtk.Widget.WidgetDragSourceSetIconPixbufMethodInfo
ResolveDockWindowMethod "dragSourceSetIconStock" o = Gtk.Widget.WidgetDragSourceSetIconStockMethodInfo
ResolveDockWindowMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
ResolveDockWindowMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
ResolveDockWindowMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
ResolveDockWindowMethod "draw" o = Gtk.Widget.WidgetDrawMethodInfo
ResolveDockWindowMethod "emitPresented" o = Dazzle.DockItem.DockItemEmitPresentedMethodInfo
ResolveDockWindowMethod "ensureStyle" o = Gtk.Widget.WidgetEnsureStyleMethodInfo
ResolveDockWindowMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
ResolveDockWindowMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
ResolveDockWindowMethod "forall" o = Gtk.Container.ContainerForallMethodInfo
ResolveDockWindowMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveDockWindowMethod "foreach" o = Gtk.Container.ContainerForeachMethodInfo
ResolveDockWindowMethod "freezeChildNotify" o = Gtk.Widget.WidgetFreezeChildNotifyMethodInfo
ResolveDockWindowMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveDockWindowMethod "fullscreen" o = Gtk.Window.WindowFullscreenMethodInfo
ResolveDockWindowMethod "fullscreenOnMonitor" o = Gtk.Window.WindowFullscreenOnMonitorMethodInfo
ResolveDockWindowMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveDockWindowMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
ResolveDockWindowMethod "grabDefault" o = Gtk.Widget.WidgetGrabDefaultMethodInfo
ResolveDockWindowMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
ResolveDockWindowMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
ResolveDockWindowMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
ResolveDockWindowMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
ResolveDockWindowMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
ResolveDockWindowMethod "hasGroup" o = Gtk.Window.WindowHasGroupMethodInfo
ResolveDockWindowMethod "hasRcStyle" o = Gtk.Widget.WidgetHasRcStyleMethodInfo
ResolveDockWindowMethod "hasScreen" o = Gtk.Widget.WidgetHasScreenMethodInfo
ResolveDockWindowMethod "hasToplevelFocus" o = Gtk.Window.WindowHasToplevelFocusMethodInfo
ResolveDockWindowMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
ResolveDockWindowMethod "hasWidgets" o = Dazzle.DockItem.DockItemHasWidgetsMethodInfo
ResolveDockWindowMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
ResolveDockWindowMethod "hideOnDelete" o = Gtk.Widget.WidgetHideOnDeleteMethodInfo
ResolveDockWindowMethod "iconify" o = Gtk.Window.WindowIconifyMethodInfo
ResolveDockWindowMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
ResolveDockWindowMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
ResolveDockWindowMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
ResolveDockWindowMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
ResolveDockWindowMethod "intersect" o = Gtk.Widget.WidgetIntersectMethodInfo
ResolveDockWindowMethod "isActive" o = Gtk.Window.WindowIsActiveMethodInfo
ResolveDockWindowMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
ResolveDockWindowMethod "isComposited" o = Gtk.Widget.WidgetIsCompositedMethodInfo
ResolveDockWindowMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
ResolveDockWindowMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveDockWindowMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
ResolveDockWindowMethod "isMaximized" o = Gtk.Window.WindowIsMaximizedMethodInfo
ResolveDockWindowMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
ResolveDockWindowMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
ResolveDockWindowMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
ResolveDockWindowMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
ResolveDockWindowMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
ResolveDockWindowMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
ResolveDockWindowMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
ResolveDockWindowMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
ResolveDockWindowMethod "maximize" o = Gtk.Window.WindowMaximizeMethodInfo
ResolveDockWindowMethod "minimize" o = Dazzle.DockItem.DockItemMinimizeMethodInfo
ResolveDockWindowMethod "mnemonicActivate" o = Gtk.Window.WindowMnemonicActivateMethodInfo
ResolveDockWindowMethod "modifyBase" o = Gtk.Widget.WidgetModifyBaseMethodInfo
ResolveDockWindowMethod "modifyBg" o = Gtk.Widget.WidgetModifyBgMethodInfo
ResolveDockWindowMethod "modifyCursor" o = Gtk.Widget.WidgetModifyCursorMethodInfo
ResolveDockWindowMethod "modifyFg" o = Gtk.Widget.WidgetModifyFgMethodInfo
ResolveDockWindowMethod "modifyFont" o = Gtk.Widget.WidgetModifyFontMethodInfo
ResolveDockWindowMethod "modifyStyle" o = Gtk.Widget.WidgetModifyStyleMethodInfo
ResolveDockWindowMethod "modifyText" o = Gtk.Widget.WidgetModifyTextMethodInfo
ResolveDockWindowMethod "move" o = Gtk.Window.WindowMoveMethodInfo
ResolveDockWindowMethod "needsAttention" o = Dazzle.DockItem.DockItemNeedsAttentionMethodInfo
ResolveDockWindowMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveDockWindowMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveDockWindowMethod "overrideBackgroundColor" o = Gtk.Widget.WidgetOverrideBackgroundColorMethodInfo
ResolveDockWindowMethod "overrideColor" o = Gtk.Widget.WidgetOverrideColorMethodInfo
ResolveDockWindowMethod "overrideCursor" o = Gtk.Widget.WidgetOverrideCursorMethodInfo
ResolveDockWindowMethod "overrideFont" o = Gtk.Widget.WidgetOverrideFontMethodInfo
ResolveDockWindowMethod "overrideSymbolicColor" o = Gtk.Widget.WidgetOverrideSymbolicColorMethodInfo
ResolveDockWindowMethod "parseGeometry" o = Gtk.Window.WindowParseGeometryMethodInfo
ResolveDockWindowMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
ResolveDockWindowMethod "path" o = Gtk.Widget.WidgetPathMethodInfo
ResolveDockWindowMethod "present" o = Gtk.Window.WindowPresentMethodInfo
ResolveDockWindowMethod "presentChild" o = Dazzle.DockItem.DockItemPresentChildMethodInfo
ResolveDockWindowMethod "presentWithTime" o = Gtk.Window.WindowPresentWithTimeMethodInfo
ResolveDockWindowMethod "propagateDraw" o = Gtk.Container.ContainerPropagateDrawMethodInfo
ResolveDockWindowMethod "propagateKeyEvent" o = Gtk.Window.WindowPropagateKeyEventMethodInfo
ResolveDockWindowMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
ResolveDockWindowMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
ResolveDockWindowMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
ResolveDockWindowMethod "queueDrawArea" o = Gtk.Widget.WidgetQueueDrawAreaMethodInfo
ResolveDockWindowMethod "queueDrawRegion" o = Gtk.Widget.WidgetQueueDrawRegionMethodInfo
ResolveDockWindowMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
ResolveDockWindowMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
ResolveDockWindowMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
ResolveDockWindowMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveDockWindowMethod "refGicon" o = Dazzle.DockItem.DockItemRefGiconMethodInfo
ResolveDockWindowMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveDockWindowMethod "regionIntersect" o = Gtk.Widget.WidgetRegionIntersectMethodInfo
ResolveDockWindowMethod "registerWindow" o = Gtk.Widget.WidgetRegisterWindowMethodInfo
ResolveDockWindowMethod "release" o = Dazzle.DockItem.DockItemReleaseMethodInfo
ResolveDockWindowMethod "remove" o = Gtk.Container.ContainerRemoveMethodInfo
ResolveDockWindowMethod "removeAccelGroup" o = Gtk.Window.WindowRemoveAccelGroupMethodInfo
ResolveDockWindowMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
ResolveDockWindowMethod "removeMnemonic" o = Gtk.Window.WindowRemoveMnemonicMethodInfo
ResolveDockWindowMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
ResolveDockWindowMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
ResolveDockWindowMethod "renderIcon" o = Gtk.Widget.WidgetRenderIconMethodInfo
ResolveDockWindowMethod "renderIconPixbuf" o = Gtk.Widget.WidgetRenderIconPixbufMethodInfo
ResolveDockWindowMethod "reparent" o = Gtk.Widget.WidgetReparentMethodInfo
ResolveDockWindowMethod "resetRcStyles" o = Gtk.Widget.WidgetResetRcStylesMethodInfo
ResolveDockWindowMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
ResolveDockWindowMethod "reshowWithInitialSize" o = Gtk.Window.WindowReshowWithInitialSizeMethodInfo
ResolveDockWindowMethod "resize" o = Gtk.Window.WindowResizeMethodInfo
ResolveDockWindowMethod "resizeChildren" o = Gtk.Container.ContainerResizeChildrenMethodInfo
ResolveDockWindowMethod "resizeGripIsVisible" o = Gtk.Window.WindowResizeGripIsVisibleMethodInfo
ResolveDockWindowMethod "resizeToGeometry" o = Gtk.Window.WindowResizeToGeometryMethodInfo
ResolveDockWindowMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveDockWindowMethod "sendExpose" o = Gtk.Widget.WidgetSendExposeMethodInfo
ResolveDockWindowMethod "sendFocusChange" o = Gtk.Widget.WidgetSendFocusChangeMethodInfo
ResolveDockWindowMethod "shapeCombineRegion" o = Gtk.Widget.WidgetShapeCombineRegionMethodInfo
ResolveDockWindowMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
ResolveDockWindowMethod "showAll" o = Gtk.Widget.WidgetShowAllMethodInfo
ResolveDockWindowMethod "showNow" o = Gtk.Widget.WidgetShowNowMethodInfo
ResolveDockWindowMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
ResolveDockWindowMethod "sizeAllocateWithBaseline" o = Gtk.Widget.WidgetSizeAllocateWithBaselineMethodInfo
ResolveDockWindowMethod "sizeRequest" o = Gtk.Widget.WidgetSizeRequestMethodInfo
ResolveDockWindowMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveDockWindowMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveDockWindowMethod "stick" o = Gtk.Window.WindowStickMethodInfo
ResolveDockWindowMethod "styleAttach" o = Gtk.Widget.WidgetStyleAttachMethodInfo
ResolveDockWindowMethod "styleGetProperty" o = Gtk.Widget.WidgetStyleGetPropertyMethodInfo
ResolveDockWindowMethod "thawChildNotify" o = Gtk.Widget.WidgetThawChildNotifyMethodInfo
ResolveDockWindowMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveDockWindowMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
ResolveDockWindowMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
ResolveDockWindowMethod "unfullscreen" o = Gtk.Window.WindowUnfullscreenMethodInfo
ResolveDockWindowMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
ResolveDockWindowMethod "unmaximize" o = Gtk.Window.WindowUnmaximizeMethodInfo
ResolveDockWindowMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
ResolveDockWindowMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
ResolveDockWindowMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveDockWindowMethod "unregisterWindow" o = Gtk.Widget.WidgetUnregisterWindowMethodInfo
ResolveDockWindowMethod "unsetFocusChain" o = Gtk.Container.ContainerUnsetFocusChainMethodInfo
ResolveDockWindowMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
ResolveDockWindowMethod "unstick" o = Gtk.Window.WindowUnstickMethodInfo
ResolveDockWindowMethod "updateVisibility" o = Dazzle.DockItem.DockItemUpdateVisibilityMethodInfo
ResolveDockWindowMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveDockWindowMethod "getAcceptFocus" o = Gtk.Window.WindowGetAcceptFocusMethodInfo
ResolveDockWindowMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
ResolveDockWindowMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
ResolveDockWindowMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
ResolveDockWindowMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
ResolveDockWindowMethod "getAllocatedSize" o = Gtk.Widget.WidgetGetAllocatedSizeMethodInfo
ResolveDockWindowMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
ResolveDockWindowMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
ResolveDockWindowMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
ResolveDockWindowMethod "getAppPaintable" o = Gtk.Widget.WidgetGetAppPaintableMethodInfo
ResolveDockWindowMethod "getApplication" o = Gtk.Window.WindowGetApplicationMethodInfo
ResolveDockWindowMethod "getAttachedTo" o = Gtk.Window.WindowGetAttachedToMethodInfo
ResolveDockWindowMethod "getBorderWidth" o = Gtk.Container.ContainerGetBorderWidthMethodInfo
ResolveDockWindowMethod "getCanClose" o = Dazzle.DockItem.DockItemGetCanCloseMethodInfo
ResolveDockWindowMethod "getCanDefault" o = Gtk.Widget.WidgetGetCanDefaultMethodInfo
ResolveDockWindowMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
ResolveDockWindowMethod "getCanMinimize" o = Dazzle.DockItem.DockItemGetCanMinimizeMethodInfo
ResolveDockWindowMethod "getChild" o = Gtk.Bin.BinGetChildMethodInfo
ResolveDockWindowMethod "getChildRequisition" o = Gtk.Widget.WidgetGetChildRequisitionMethodInfo
ResolveDockWindowMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
ResolveDockWindowMethod "getChildren" o = Gtk.Container.ContainerGetChildrenMethodInfo
ResolveDockWindowMethod "getClip" o = Gtk.Widget.WidgetGetClipMethodInfo
ResolveDockWindowMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
ResolveDockWindowMethod "getCompositeName" o = Gtk.Widget.WidgetGetCompositeNameMethodInfo
ResolveDockWindowMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveDockWindowMethod "getDecorated" o = Gtk.Window.WindowGetDecoratedMethodInfo
ResolveDockWindowMethod "getDefaultSize" o = Gtk.Window.WindowGetDefaultSizeMethodInfo
ResolveDockWindowMethod "getDefaultWidget" o = Gtk.Window.WindowGetDefaultWidgetMethodInfo
ResolveDockWindowMethod "getDeletable" o = Gtk.Window.WindowGetDeletableMethodInfo
ResolveDockWindowMethod "getDestroyWithParent" o = Gtk.Window.WindowGetDestroyWithParentMethodInfo
ResolveDockWindowMethod "getDeviceEnabled" o = Gtk.Widget.WidgetGetDeviceEnabledMethodInfo
ResolveDockWindowMethod "getDeviceEvents" o = Gtk.Widget.WidgetGetDeviceEventsMethodInfo
ResolveDockWindowMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
ResolveDockWindowMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
ResolveDockWindowMethod "getDoubleBuffered" o = Gtk.Widget.WidgetGetDoubleBufferedMethodInfo
ResolveDockWindowMethod "getEvents" o = Gtk.Widget.WidgetGetEventsMethodInfo
ResolveDockWindowMethod "getFocus" o = Gtk.Window.WindowGetFocusMethodInfo
ResolveDockWindowMethod "getFocusChain" o = Gtk.Container.ContainerGetFocusChainMethodInfo
ResolveDockWindowMethod "getFocusChild" o = Gtk.Container.ContainerGetFocusChildMethodInfo
ResolveDockWindowMethod "getFocusHadjustment" o = Gtk.Container.ContainerGetFocusHadjustmentMethodInfo
ResolveDockWindowMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
ResolveDockWindowMethod "getFocusOnMap" o = Gtk.Window.WindowGetFocusOnMapMethodInfo
ResolveDockWindowMethod "getFocusVadjustment" o = Gtk.Container.ContainerGetFocusVadjustmentMethodInfo
ResolveDockWindowMethod "getFocusVisible" o = Gtk.Window.WindowGetFocusVisibleMethodInfo
ResolveDockWindowMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
ResolveDockWindowMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
ResolveDockWindowMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
ResolveDockWindowMethod "getGravity" o = Gtk.Window.WindowGetGravityMethodInfo
ResolveDockWindowMethod "getGroup" o = Gtk.Window.WindowGetGroupMethodInfo
ResolveDockWindowMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
ResolveDockWindowMethod "getHasResizeGrip" o = Gtk.Window.WindowGetHasResizeGripMethodInfo
ResolveDockWindowMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
ResolveDockWindowMethod "getHasWindow" o = Gtk.Widget.WidgetGetHasWindowMethodInfo
ResolveDockWindowMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
ResolveDockWindowMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
ResolveDockWindowMethod "getHideTitlebarWhenMaximized" o = Gtk.Window.WindowGetHideTitlebarWhenMaximizedMethodInfo
ResolveDockWindowMethod "getIcon" o = Gtk.Window.WindowGetIconMethodInfo
ResolveDockWindowMethod "getIconList" o = Gtk.Window.WindowGetIconListMethodInfo
ResolveDockWindowMethod "getIconName" o = Gtk.Window.WindowGetIconNameMethodInfo
ResolveDockWindowMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
ResolveDockWindowMethod "getManager" o = Dazzle.DockItem.DockItemGetManagerMethodInfo
ResolveDockWindowMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
ResolveDockWindowMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
ResolveDockWindowMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
ResolveDockWindowMethod "getMarginLeft" o = Gtk.Widget.WidgetGetMarginLeftMethodInfo
ResolveDockWindowMethod "getMarginRight" o = Gtk.Widget.WidgetGetMarginRightMethodInfo
ResolveDockWindowMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
ResolveDockWindowMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
ResolveDockWindowMethod "getMnemonicModifier" o = Gtk.Window.WindowGetMnemonicModifierMethodInfo
ResolveDockWindowMethod "getMnemonicsVisible" o = Gtk.Window.WindowGetMnemonicsVisibleMethodInfo
ResolveDockWindowMethod "getModal" o = Gtk.Window.WindowGetModalMethodInfo
ResolveDockWindowMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
ResolveDockWindowMethod "getModifierStyle" o = Gtk.Widget.WidgetGetModifierStyleMethodInfo
ResolveDockWindowMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
ResolveDockWindowMethod "getNoShowAll" o = Gtk.Widget.WidgetGetNoShowAllMethodInfo
ResolveDockWindowMethod "getOpacity" o = Gtk.Window.WindowGetOpacityMethodInfo
ResolveDockWindowMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
ResolveDockWindowMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
ResolveDockWindowMethod "getParentWindow" o = Gtk.Widget.WidgetGetParentWindowMethodInfo
ResolveDockWindowMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
ResolveDockWindowMethod "getPathForChild" o = Gtk.Container.ContainerGetPathForChildMethodInfo
ResolveDockWindowMethod "getPointer" o = Gtk.Widget.WidgetGetPointerMethodInfo
ResolveDockWindowMethod "getPosition" o = Gtk.Window.WindowGetPositionMethodInfo
ResolveDockWindowMethod "getPreferredHeight" o = Gtk.Widget.WidgetGetPreferredHeightMethodInfo
ResolveDockWindowMethod "getPreferredHeightAndBaselineForWidth" o = Gtk.Widget.WidgetGetPreferredHeightAndBaselineForWidthMethodInfo
ResolveDockWindowMethod "getPreferredHeightForWidth" o = Gtk.Widget.WidgetGetPreferredHeightForWidthMethodInfo
ResolveDockWindowMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
ResolveDockWindowMethod "getPreferredWidth" o = Gtk.Widget.WidgetGetPreferredWidthMethodInfo
ResolveDockWindowMethod "getPreferredWidthForHeight" o = Gtk.Widget.WidgetGetPreferredWidthForHeightMethodInfo
ResolveDockWindowMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveDockWindowMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveDockWindowMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
ResolveDockWindowMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
ResolveDockWindowMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
ResolveDockWindowMethod "getRequisition" o = Gtk.Widget.WidgetGetRequisitionMethodInfo
ResolveDockWindowMethod "getResizable" o = Gtk.Window.WindowGetResizableMethodInfo
ResolveDockWindowMethod "getResizeGripArea" o = Gtk.Window.WindowGetResizeGripAreaMethodInfo
ResolveDockWindowMethod "getResizeMode" o = Gtk.Container.ContainerGetResizeModeMethodInfo
ResolveDockWindowMethod "getRole" o = Gtk.Window.WindowGetRoleMethodInfo
ResolveDockWindowMethod "getRootWindow" o = Gtk.Widget.WidgetGetRootWindowMethodInfo
ResolveDockWindowMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
ResolveDockWindowMethod "getScreen" o = Gtk.Window.WindowGetScreenMethodInfo
ResolveDockWindowMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
ResolveDockWindowMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
ResolveDockWindowMethod "getSize" o = Gtk.Window.WindowGetSizeMethodInfo
ResolveDockWindowMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
ResolveDockWindowMethod "getSkipPagerHint" o = Gtk.Window.WindowGetSkipPagerHintMethodInfo
ResolveDockWindowMethod "getSkipTaskbarHint" o = Gtk.Window.WindowGetSkipTaskbarHintMethodInfo
ResolveDockWindowMethod "getState" o = Gtk.Widget.WidgetGetStateMethodInfo
ResolveDockWindowMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
ResolveDockWindowMethod "getStyle" o = Gtk.Widget.WidgetGetStyleMethodInfo
ResolveDockWindowMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
ResolveDockWindowMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
ResolveDockWindowMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
ResolveDockWindowMethod "getTitle" o = Gtk.Window.WindowGetTitleMethodInfo
ResolveDockWindowMethod "getTitlebar" o = Gtk.Window.WindowGetTitlebarMethodInfo
ResolveDockWindowMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
ResolveDockWindowMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
ResolveDockWindowMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
ResolveDockWindowMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
ResolveDockWindowMethod "getTransientFor" o = Gtk.Window.WindowGetTransientForMethodInfo
ResolveDockWindowMethod "getTypeHint" o = Gtk.Window.WindowGetTypeHintMethodInfo
ResolveDockWindowMethod "getUrgencyHint" o = Gtk.Window.WindowGetUrgencyHintMethodInfo
ResolveDockWindowMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
ResolveDockWindowMethod "getValignWithBaseline" o = Gtk.Widget.WidgetGetValignWithBaselineMethodInfo
ResolveDockWindowMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
ResolveDockWindowMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
ResolveDockWindowMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
ResolveDockWindowMethod "getVisual" o = Gtk.Widget.WidgetGetVisualMethodInfo
ResolveDockWindowMethod "getWindow" o = Gtk.Widget.WidgetGetWindowMethodInfo
ResolveDockWindowMethod "getWindowType" o = Gtk.Window.WindowGetWindowTypeMethodInfo
ResolveDockWindowMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
ResolveDockWindowMethod "setAcceptFocus" o = Gtk.Window.WindowSetAcceptFocusMethodInfo
ResolveDockWindowMethod "setAllocation" o = Gtk.Widget.WidgetSetAllocationMethodInfo
ResolveDockWindowMethod "setAppPaintable" o = Gtk.Widget.WidgetSetAppPaintableMethodInfo
ResolveDockWindowMethod "setApplication" o = Gtk.Window.WindowSetApplicationMethodInfo
ResolveDockWindowMethod "setAttachedTo" o = Gtk.Window.WindowSetAttachedToMethodInfo
ResolveDockWindowMethod "setBorderWidth" o = Gtk.Container.ContainerSetBorderWidthMethodInfo
ResolveDockWindowMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
ResolveDockWindowMethod "setCanDefault" o = Gtk.Widget.WidgetSetCanDefaultMethodInfo
ResolveDockWindowMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
ResolveDockWindowMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
ResolveDockWindowMethod "setClip" o = Gtk.Widget.WidgetSetClipMethodInfo
ResolveDockWindowMethod "setCompositeName" o = Gtk.Widget.WidgetSetCompositeNameMethodInfo
ResolveDockWindowMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveDockWindowMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveDockWindowMethod "setDecorated" o = Gtk.Window.WindowSetDecoratedMethodInfo
ResolveDockWindowMethod "setDefault" o = Gtk.Window.WindowSetDefaultMethodInfo
ResolveDockWindowMethod "setDefaultGeometry" o = Gtk.Window.WindowSetDefaultGeometryMethodInfo
ResolveDockWindowMethod "setDefaultSize" o = Gtk.Window.WindowSetDefaultSizeMethodInfo
ResolveDockWindowMethod "setDeletable" o = Gtk.Window.WindowSetDeletableMethodInfo
ResolveDockWindowMethod "setDestroyWithParent" o = Gtk.Window.WindowSetDestroyWithParentMethodInfo
ResolveDockWindowMethod "setDeviceEnabled" o = Gtk.Widget.WidgetSetDeviceEnabledMethodInfo
ResolveDockWindowMethod "setDeviceEvents" o = Gtk.Widget.WidgetSetDeviceEventsMethodInfo
ResolveDockWindowMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
ResolveDockWindowMethod "setDoubleBuffered" o = Gtk.Widget.WidgetSetDoubleBufferedMethodInfo
ResolveDockWindowMethod "setEvents" o = Gtk.Widget.WidgetSetEventsMethodInfo
ResolveDockWindowMethod "setFocus" o = Gtk.Window.WindowSetFocusMethodInfo
ResolveDockWindowMethod "setFocusChain" o = Gtk.Container.ContainerSetFocusChainMethodInfo
ResolveDockWindowMethod "setFocusChild" o = Gtk.Container.ContainerSetFocusChildMethodInfo
ResolveDockWindowMethod "setFocusHadjustment" o = Gtk.Container.ContainerSetFocusHadjustmentMethodInfo
ResolveDockWindowMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
ResolveDockWindowMethod "setFocusOnMap" o = Gtk.Window.WindowSetFocusOnMapMethodInfo
ResolveDockWindowMethod "setFocusVadjustment" o = Gtk.Container.ContainerSetFocusVadjustmentMethodInfo
ResolveDockWindowMethod "setFocusVisible" o = Gtk.Window.WindowSetFocusVisibleMethodInfo
ResolveDockWindowMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
ResolveDockWindowMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
ResolveDockWindowMethod "setGeometryHints" o = Gtk.Window.WindowSetGeometryHintsMethodInfo
ResolveDockWindowMethod "setGravity" o = Gtk.Window.WindowSetGravityMethodInfo
ResolveDockWindowMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
ResolveDockWindowMethod "setHasResizeGrip" o = Gtk.Window.WindowSetHasResizeGripMethodInfo
ResolveDockWindowMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
ResolveDockWindowMethod "setHasUserRefCount" o = Gtk.Window.WindowSetHasUserRefCountMethodInfo
ResolveDockWindowMethod "setHasWindow" o = Gtk.Widget.WidgetSetHasWindowMethodInfo
ResolveDockWindowMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
ResolveDockWindowMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
ResolveDockWindowMethod "setHideTitlebarWhenMaximized" o = Gtk.Window.WindowSetHideTitlebarWhenMaximizedMethodInfo
ResolveDockWindowMethod "setIcon" o = Gtk.Window.WindowSetIconMethodInfo
ResolveDockWindowMethod "setIconFromFile" o = Gtk.Window.WindowSetIconFromFileMethodInfo
ResolveDockWindowMethod "setIconList" o = Gtk.Window.WindowSetIconListMethodInfo
ResolveDockWindowMethod "setIconName" o = Gtk.Window.WindowSetIconNameMethodInfo
ResolveDockWindowMethod "setKeepAbove" o = Gtk.Window.WindowSetKeepAboveMethodInfo
ResolveDockWindowMethod "setKeepBelow" o = Gtk.Window.WindowSetKeepBelowMethodInfo
ResolveDockWindowMethod "setManager" o = Dazzle.DockItem.DockItemSetManagerMethodInfo
ResolveDockWindowMethod "setMapped" o = Gtk.Widget.WidgetSetMappedMethodInfo
ResolveDockWindowMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
ResolveDockWindowMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
ResolveDockWindowMethod "setMarginLeft" o = Gtk.Widget.WidgetSetMarginLeftMethodInfo
ResolveDockWindowMethod "setMarginRight" o = Gtk.Widget.WidgetSetMarginRightMethodInfo
ResolveDockWindowMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
ResolveDockWindowMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
ResolveDockWindowMethod "setMnemonicModifier" o = Gtk.Window.WindowSetMnemonicModifierMethodInfo
ResolveDockWindowMethod "setMnemonicsVisible" o = Gtk.Window.WindowSetMnemonicsVisibleMethodInfo
ResolveDockWindowMethod "setModal" o = Gtk.Window.WindowSetModalMethodInfo
ResolveDockWindowMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
ResolveDockWindowMethod "setNoShowAll" o = Gtk.Widget.WidgetSetNoShowAllMethodInfo
ResolveDockWindowMethod "setOpacity" o = Gtk.Window.WindowSetOpacityMethodInfo
ResolveDockWindowMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
ResolveDockWindowMethod "setParentWindow" o = Gtk.Widget.WidgetSetParentWindowMethodInfo
ResolveDockWindowMethod "setPosition" o = Gtk.Window.WindowSetPositionMethodInfo
ResolveDockWindowMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveDockWindowMethod "setRealized" o = Gtk.Widget.WidgetSetRealizedMethodInfo
ResolveDockWindowMethod "setReallocateRedraws" o = Gtk.Container.ContainerSetReallocateRedrawsMethodInfo
ResolveDockWindowMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
ResolveDockWindowMethod "setRedrawOnAllocate" o = Gtk.Widget.WidgetSetRedrawOnAllocateMethodInfo
ResolveDockWindowMethod "setResizable" o = Gtk.Window.WindowSetResizableMethodInfo
ResolveDockWindowMethod "setResizeMode" o = Gtk.Container.ContainerSetResizeModeMethodInfo
ResolveDockWindowMethod "setRole" o = Gtk.Window.WindowSetRoleMethodInfo
ResolveDockWindowMethod "setScreen" o = Gtk.Window.WindowSetScreenMethodInfo
ResolveDockWindowMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
ResolveDockWindowMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
ResolveDockWindowMethod "setSkipPagerHint" o = Gtk.Window.WindowSetSkipPagerHintMethodInfo
ResolveDockWindowMethod "setSkipTaskbarHint" o = Gtk.Window.WindowSetSkipTaskbarHintMethodInfo
ResolveDockWindowMethod "setStartupId" o = Gtk.Window.WindowSetStartupIdMethodInfo
ResolveDockWindowMethod "setState" o = Gtk.Widget.WidgetSetStateMethodInfo
ResolveDockWindowMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
ResolveDockWindowMethod "setStyle" o = Gtk.Widget.WidgetSetStyleMethodInfo
ResolveDockWindowMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
ResolveDockWindowMethod "setTitle" o = Gtk.Window.WindowSetTitleMethodInfo
ResolveDockWindowMethod "setTitlebar" o = Gtk.Window.WindowSetTitlebarMethodInfo
ResolveDockWindowMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
ResolveDockWindowMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
ResolveDockWindowMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
ResolveDockWindowMethod "setTransientFor" o = Gtk.Window.WindowSetTransientForMethodInfo
ResolveDockWindowMethod "setTypeHint" o = Gtk.Window.WindowSetTypeHintMethodInfo
ResolveDockWindowMethod "setUrgencyHint" o = Gtk.Window.WindowSetUrgencyHintMethodInfo
ResolveDockWindowMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
ResolveDockWindowMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
ResolveDockWindowMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
ResolveDockWindowMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
ResolveDockWindowMethod "setVisual" o = Gtk.Widget.WidgetSetVisualMethodInfo
ResolveDockWindowMethod "setWindow" o = Gtk.Widget.WidgetSetWindowMethodInfo
ResolveDockWindowMethod "setWmclass" o = Gtk.Window.WindowSetWmclassMethodInfo
ResolveDockWindowMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveDockWindowMethod t DockWindow, O.OverloadedMethod info DockWindow p) => OL.IsLabel t (DockWindow -> 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 ~ ResolveDockWindowMethod t DockWindow, O.OverloadedMethod info DockWindow p, R.HasField t DockWindow p) => R.HasField t DockWindow p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveDockWindowMethod t DockWindow, O.OverloadedMethodInfo info DockWindow) => OL.IsLabel t (O.MethodProxy info DockWindow) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DockWindow
type instance O.AttributeList DockWindow = DockWindowAttributeList
type DockWindowAttributeList = ('[ '("acceptFocus", Gtk.Window.WindowAcceptFocusPropertyInfo), '("appPaintable", Gtk.Widget.WidgetAppPaintablePropertyInfo), '("application", Gtk.Window.WindowApplicationPropertyInfo), '("attachedTo", Gtk.Window.WindowAttachedToPropertyInfo), '("borderWidth", Gtk.Container.ContainerBorderWidthPropertyInfo), '("canDefault", Gtk.Widget.WidgetCanDefaultPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("child", Gtk.Container.ContainerChildPropertyInfo), '("compositeChild", Gtk.Widget.WidgetCompositeChildPropertyInfo), '("decorated", Gtk.Window.WindowDecoratedPropertyInfo), '("defaultHeight", Gtk.Window.WindowDefaultHeightPropertyInfo), '("defaultWidth", Gtk.Window.WindowDefaultWidthPropertyInfo), '("deletable", Gtk.Window.WindowDeletablePropertyInfo), '("destroyWithParent", Gtk.Window.WindowDestroyWithParentPropertyInfo), '("doubleBuffered", Gtk.Widget.WidgetDoubleBufferedPropertyInfo), '("events", Gtk.Widget.WidgetEventsPropertyInfo), '("expand", Gtk.Widget.WidgetExpandPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("focusOnMap", Gtk.Window.WindowFocusOnMapPropertyInfo), '("focusVisible", Gtk.Window.WindowFocusVisiblePropertyInfo), '("gravity", Gtk.Window.WindowGravityPropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasResizeGrip", Gtk.Window.WindowHasResizeGripPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("hasToplevelFocus", Gtk.Window.WindowHasToplevelFocusPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("hideTitlebarWhenMaximized", Gtk.Window.WindowHideTitlebarWhenMaximizedPropertyInfo), '("icon", Gtk.Window.WindowIconPropertyInfo), '("iconName", Gtk.Window.WindowIconNamePropertyInfo), '("isActive", Gtk.Window.WindowIsActivePropertyInfo), '("isFocus", Gtk.Widget.WidgetIsFocusPropertyInfo), '("isMaximized", Gtk.Window.WindowIsMaximizedPropertyInfo), '("manager", Dazzle.Dock.DockManagerPropertyInfo), '("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), '("mnemonicsVisible", Gtk.Window.WindowMnemonicsVisiblePropertyInfo), '("modal", Gtk.Window.WindowModalPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("noShowAll", Gtk.Widget.WidgetNoShowAllPropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("resizable", Gtk.Window.WindowResizablePropertyInfo), '("resizeGripVisible", Gtk.Window.WindowResizeGripVisiblePropertyInfo), '("resizeMode", Gtk.Container.ContainerResizeModePropertyInfo), '("role", Gtk.Window.WindowRolePropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("screen", Gtk.Window.WindowScreenPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("skipPagerHint", Gtk.Window.WindowSkipPagerHintPropertyInfo), '("skipTaskbarHint", Gtk.Window.WindowSkipTaskbarHintPropertyInfo), '("startupId", Gtk.Window.WindowStartupIdPropertyInfo), '("style", Gtk.Widget.WidgetStylePropertyInfo), '("title", Gtk.Window.WindowTitlePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("transientFor", Gtk.Window.WindowTransientForPropertyInfo), '("type", Gtk.Window.WindowTypePropertyInfo), '("typeHint", Gtk.Window.WindowTypeHintPropertyInfo), '("urgencyHint", Gtk.Window.WindowUrgencyHintPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo), '("window", Gtk.Widget.WidgetWindowPropertyInfo), '("windowPosition", Gtk.Window.WindowWindowPositionPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DockWindow = DockWindowSignalList
type DockWindowSignalList = ('[ '("accelClosuresChanged", Gtk.Widget.WidgetAccelClosuresChangedSignalInfo), '("activateDefault", Gtk.Window.WindowActivateDefaultSignalInfo), '("activateFocus", Gtk.Window.WindowActivateFocusSignalInfo), '("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), '("enableDebugging", Gtk.Window.WindowEnableDebuggingSignalInfo), '("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), '("keysChanged", Gtk.Window.WindowKeysChangedSignalInfo), '("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), '("setFocus", Gtk.Window.WindowSetFocusSignalInfo), '("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_window_new" dzl_dock_window_new ::
IO (Ptr DockWindow)
dockWindowNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m DockWindow
dockWindowNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m DockWindow
dockWindowNew = IO DockWindow -> m DockWindow
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DockWindow -> m DockWindow) -> IO DockWindow -> m DockWindow
forall a b. (a -> b) -> a -> b
$ do
Ptr DockWindow
result <- IO (Ptr DockWindow)
dzl_dock_window_new
Text -> Ptr DockWindow -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dockWindowNew" Ptr DockWindow
result
DockWindow
result' <- ((ManagedPtr DockWindow -> DockWindow)
-> Ptr DockWindow -> IO DockWindow
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DockWindow -> DockWindow
DockWindow) Ptr DockWindow
result
DockWindow -> IO DockWindow
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return DockWindow
result'
#if defined(ENABLE_OVERLOADING)
#endif