{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Dazzle.Interfaces.Dock
(
Dock(..) ,
IsDock ,
toDock ,
#if defined(ENABLE_OVERLOADING)
ResolveDockMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DockManagerPropertyInfo ,
#endif
clearDockManager ,
constructDockManager ,
#if defined(ENABLE_OVERLOADING)
dockManager ,
#endif
getDockManager ,
setDockManager ,
) 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 {-# SOURCE #-} qualified GI.Dazzle.Objects.DockManager as Dazzle.DockManager
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Objects.Container as Gtk.Container
import qualified GI.Gtk.Objects.Widget as Gtk.Widget
#else
import {-# SOURCE #-} qualified GI.Dazzle.Objects.DockManager as Dazzle.DockManager
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Objects.Container as Gtk.Container
import qualified GI.Gtk.Objects.Widget as Gtk.Widget
#endif
newtype Dock = Dock (SP.ManagedPtr Dock)
deriving (Dock -> Dock -> Bool
(Dock -> Dock -> Bool) -> (Dock -> Dock -> Bool) -> Eq Dock
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Dock -> Dock -> Bool
== :: Dock -> Dock -> Bool
$c/= :: Dock -> Dock -> Bool
/= :: Dock -> Dock -> Bool
Eq)
instance SP.ManagedPtrNewtype Dock where
toManagedPtr :: Dock -> ManagedPtr Dock
toManagedPtr (Dock ManagedPtr Dock
p) = ManagedPtr Dock
p
foreign import ccall "dzl_dock_get_type"
c_dzl_dock_get_type :: IO B.Types.GType
instance B.Types.TypedObject Dock where
glibType :: IO GType
glibType = IO GType
c_dzl_dock_get_type
instance B.Types.GObject Dock
class (SP.GObject o, O.IsDescendantOf Dock o) => IsDock o
instance (SP.GObject o, O.IsDescendantOf Dock o) => IsDock o
instance O.HasParentTypes Dock
type instance O.ParentTypes Dock = '[GObject.Object.Object, Gtk.Container.Container, Gtk.Widget.Widget]
toDock :: (MIO.MonadIO m, IsDock o) => o -> m Dock
toDock :: forall (m :: * -> *) o. (MonadIO m, IsDock o) => o -> m Dock
toDock = IO Dock -> m Dock
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Dock -> m Dock) -> (o -> IO Dock) -> o -> m Dock
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Dock -> Dock) -> o -> IO Dock
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Dock -> Dock
Dock
instance B.GValue.IsGValue (Maybe Dock) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_dzl_dock_get_type
gvalueSet_ :: Ptr GValue -> Maybe Dock -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Dock
P.Nothing = Ptr GValue -> Ptr Dock -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Dock
forall a. Ptr a
FP.nullPtr :: FP.Ptr Dock)
gvalueSet_ Ptr GValue
gv (P.Just Dock
obj) = Dock -> (Ptr Dock -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Dock
obj (Ptr GValue -> Ptr Dock -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe Dock)
gvalueGet_ Ptr GValue
gv = do
Ptr Dock
ptr <- Ptr GValue -> IO (Ptr Dock)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Dock)
if Ptr Dock
ptr Ptr Dock -> Ptr Dock -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Dock
forall a. Ptr a
FP.nullPtr
then Dock -> Maybe Dock
forall a. a -> Maybe a
P.Just (Dock -> Maybe Dock) -> IO Dock -> IO (Maybe Dock)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Dock -> Dock) -> Ptr Dock -> IO Dock
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Dock -> Dock
Dock Ptr Dock
ptr
else Maybe Dock -> IO (Maybe Dock)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Dock
forall a. Maybe a
P.Nothing
getDockManager :: (MonadIO m, IsDock o) => o -> m (Maybe Dazzle.DockManager.DockManager)
getDockManager :: forall (m :: * -> *) o.
(MonadIO m, IsDock o) =>
o -> m (Maybe DockManager)
getDockManager 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
setDockManager :: (MonadIO m, IsDock o, Dazzle.DockManager.IsDockManager a) => o -> a -> m ()
setDockManager :: forall (m :: * -> *) o a.
(MonadIO m, IsDock o, IsDockManager a) =>
o -> a -> m ()
setDockManager 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)
constructDockManager :: (IsDock o, MIO.MonadIO m, Dazzle.DockManager.IsDockManager a) => a -> m (GValueConstruct o)
constructDockManager :: forall o (m :: * -> *) a.
(IsDock o, MonadIO m, IsDockManager a) =>
a -> m (GValueConstruct o)
constructDockManager 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)
clearDockManager :: (MonadIO m, IsDock o) => o -> m ()
clearDockManager :: forall (m :: * -> *) o. (MonadIO m, IsDock o) => o -> m ()
clearDockManager 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 DockManagerPropertyInfo
instance AttrInfo DockManagerPropertyInfo where
type AttrAllowedOps DockManagerPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DockManagerPropertyInfo = IsDock
type AttrSetTypeConstraint DockManagerPropertyInfo = Dazzle.DockManager.IsDockManager
type AttrTransferTypeConstraint DockManagerPropertyInfo = Dazzle.DockManager.IsDockManager
type AttrTransferType DockManagerPropertyInfo = Dazzle.DockManager.DockManager
type AttrGetType DockManagerPropertyInfo = (Maybe Dazzle.DockManager.DockManager)
type AttrLabel DockManagerPropertyInfo = "manager"
type AttrOrigin DockManagerPropertyInfo = Dock
attrGet = getDockManager
attrSet = setDockManager
attrTransfer _ v = do
unsafeCastTo Dazzle.DockManager.DockManager v
attrConstruct = constructDockManager
attrClear = clearDockManager
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Interfaces.Dock.manager"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Interfaces-Dock.html#g:attr:manager"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Dock
type instance O.AttributeList Dock = DockAttributeList
type DockAttributeList = ('[ '("appPaintable", Gtk.Widget.WidgetAppPaintablePropertyInfo), '("borderWidth", Gtk.Container.ContainerBorderWidthPropertyInfo), '("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), '("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), '("isFocus", Gtk.Widget.WidgetIsFocusPropertyInfo), '("manager", 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), '("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), '("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)
dockManager :: AttrLabelProxy "manager"
dockManager = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveDockMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveDockMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
ResolveDockMethod "add" o = Gtk.Container.ContainerAddMethodInfo
ResolveDockMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
ResolveDockMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
ResolveDockMethod "addDeviceEvents" o = Gtk.Widget.WidgetAddDeviceEventsMethodInfo
ResolveDockMethod "addEvents" o = Gtk.Widget.WidgetAddEventsMethodInfo
ResolveDockMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
ResolveDockMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
ResolveDockMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveDockMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveDockMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
ResolveDockMethod "checkResize" o = Gtk.Container.ContainerCheckResizeMethodInfo
ResolveDockMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
ResolveDockMethod "childGetProperty" o = Gtk.Container.ContainerChildGetPropertyMethodInfo
ResolveDockMethod "childNotify" o = Gtk.Container.ContainerChildNotifyMethodInfo
ResolveDockMethod "childNotifyByPspec" o = Gtk.Container.ContainerChildNotifyByPspecMethodInfo
ResolveDockMethod "childSetProperty" o = Gtk.Container.ContainerChildSetPropertyMethodInfo
ResolveDockMethod "childType" o = Gtk.Container.ContainerChildTypeMethodInfo
ResolveDockMethod "classPath" o = Gtk.Widget.WidgetClassPathMethodInfo
ResolveDockMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
ResolveDockMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
ResolveDockMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
ResolveDockMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
ResolveDockMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
ResolveDockMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
ResolveDockMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
ResolveDockMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
ResolveDockMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
ResolveDockMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
ResolveDockMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
ResolveDockMethod "dragBeginWithCoordinates" o = Gtk.Widget.WidgetDragBeginWithCoordinatesMethodInfo
ResolveDockMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
ResolveDockMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
ResolveDockMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
ResolveDockMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
ResolveDockMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
ResolveDockMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
ResolveDockMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
ResolveDockMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
ResolveDockMethod "dragDestSetProxy" o = Gtk.Widget.WidgetDragDestSetProxyMethodInfo
ResolveDockMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
ResolveDockMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
ResolveDockMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
ResolveDockMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
ResolveDockMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
ResolveDockMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
ResolveDockMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
ResolveDockMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
ResolveDockMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
ResolveDockMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
ResolveDockMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
ResolveDockMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
ResolveDockMethod "dragSourceSetIconPixbuf" o = Gtk.Widget.WidgetDragSourceSetIconPixbufMethodInfo
ResolveDockMethod "dragSourceSetIconStock" o = Gtk.Widget.WidgetDragSourceSetIconStockMethodInfo
ResolveDockMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
ResolveDockMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
ResolveDockMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
ResolveDockMethod "draw" o = Gtk.Widget.WidgetDrawMethodInfo
ResolveDockMethod "ensureStyle" o = Gtk.Widget.WidgetEnsureStyleMethodInfo
ResolveDockMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
ResolveDockMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
ResolveDockMethod "forall" o = Gtk.Container.ContainerForallMethodInfo
ResolveDockMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveDockMethod "foreach" o = Gtk.Container.ContainerForeachMethodInfo
ResolveDockMethod "freezeChildNotify" o = Gtk.Widget.WidgetFreezeChildNotifyMethodInfo
ResolveDockMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveDockMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveDockMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
ResolveDockMethod "grabDefault" o = Gtk.Widget.WidgetGrabDefaultMethodInfo
ResolveDockMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
ResolveDockMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
ResolveDockMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
ResolveDockMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
ResolveDockMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
ResolveDockMethod "hasRcStyle" o = Gtk.Widget.WidgetHasRcStyleMethodInfo
ResolveDockMethod "hasScreen" o = Gtk.Widget.WidgetHasScreenMethodInfo
ResolveDockMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
ResolveDockMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
ResolveDockMethod "hideOnDelete" o = Gtk.Widget.WidgetHideOnDeleteMethodInfo
ResolveDockMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
ResolveDockMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
ResolveDockMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
ResolveDockMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
ResolveDockMethod "intersect" o = Gtk.Widget.WidgetIntersectMethodInfo
ResolveDockMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
ResolveDockMethod "isComposited" o = Gtk.Widget.WidgetIsCompositedMethodInfo
ResolveDockMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
ResolveDockMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveDockMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
ResolveDockMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
ResolveDockMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
ResolveDockMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
ResolveDockMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
ResolveDockMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
ResolveDockMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
ResolveDockMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
ResolveDockMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
ResolveDockMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
ResolveDockMethod "modifyBase" o = Gtk.Widget.WidgetModifyBaseMethodInfo
ResolveDockMethod "modifyBg" o = Gtk.Widget.WidgetModifyBgMethodInfo
ResolveDockMethod "modifyCursor" o = Gtk.Widget.WidgetModifyCursorMethodInfo
ResolveDockMethod "modifyFg" o = Gtk.Widget.WidgetModifyFgMethodInfo
ResolveDockMethod "modifyFont" o = Gtk.Widget.WidgetModifyFontMethodInfo
ResolveDockMethod "modifyStyle" o = Gtk.Widget.WidgetModifyStyleMethodInfo
ResolveDockMethod "modifyText" o = Gtk.Widget.WidgetModifyTextMethodInfo
ResolveDockMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveDockMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveDockMethod "overrideBackgroundColor" o = Gtk.Widget.WidgetOverrideBackgroundColorMethodInfo
ResolveDockMethod "overrideColor" o = Gtk.Widget.WidgetOverrideColorMethodInfo
ResolveDockMethod "overrideCursor" o = Gtk.Widget.WidgetOverrideCursorMethodInfo
ResolveDockMethod "overrideFont" o = Gtk.Widget.WidgetOverrideFontMethodInfo
ResolveDockMethod "overrideSymbolicColor" o = Gtk.Widget.WidgetOverrideSymbolicColorMethodInfo
ResolveDockMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
ResolveDockMethod "path" o = Gtk.Widget.WidgetPathMethodInfo
ResolveDockMethod "propagateDraw" o = Gtk.Container.ContainerPropagateDrawMethodInfo
ResolveDockMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
ResolveDockMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
ResolveDockMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
ResolveDockMethod "queueDrawArea" o = Gtk.Widget.WidgetQueueDrawAreaMethodInfo
ResolveDockMethod "queueDrawRegion" o = Gtk.Widget.WidgetQueueDrawRegionMethodInfo
ResolveDockMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
ResolveDockMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
ResolveDockMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
ResolveDockMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveDockMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveDockMethod "regionIntersect" o = Gtk.Widget.WidgetRegionIntersectMethodInfo
ResolveDockMethod "registerWindow" o = Gtk.Widget.WidgetRegisterWindowMethodInfo
ResolveDockMethod "remove" o = Gtk.Container.ContainerRemoveMethodInfo
ResolveDockMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
ResolveDockMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
ResolveDockMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
ResolveDockMethod "renderIcon" o = Gtk.Widget.WidgetRenderIconMethodInfo
ResolveDockMethod "renderIconPixbuf" o = Gtk.Widget.WidgetRenderIconPixbufMethodInfo
ResolveDockMethod "reparent" o = Gtk.Widget.WidgetReparentMethodInfo
ResolveDockMethod "resetRcStyles" o = Gtk.Widget.WidgetResetRcStylesMethodInfo
ResolveDockMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
ResolveDockMethod "resizeChildren" o = Gtk.Container.ContainerResizeChildrenMethodInfo
ResolveDockMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveDockMethod "sendExpose" o = Gtk.Widget.WidgetSendExposeMethodInfo
ResolveDockMethod "sendFocusChange" o = Gtk.Widget.WidgetSendFocusChangeMethodInfo
ResolveDockMethod "shapeCombineRegion" o = Gtk.Widget.WidgetShapeCombineRegionMethodInfo
ResolveDockMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
ResolveDockMethod "showAll" o = Gtk.Widget.WidgetShowAllMethodInfo
ResolveDockMethod "showNow" o = Gtk.Widget.WidgetShowNowMethodInfo
ResolveDockMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
ResolveDockMethod "sizeAllocateWithBaseline" o = Gtk.Widget.WidgetSizeAllocateWithBaselineMethodInfo
ResolveDockMethod "sizeRequest" o = Gtk.Widget.WidgetSizeRequestMethodInfo
ResolveDockMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveDockMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveDockMethod "styleAttach" o = Gtk.Widget.WidgetStyleAttachMethodInfo
ResolveDockMethod "styleGetProperty" o = Gtk.Widget.WidgetStyleGetPropertyMethodInfo
ResolveDockMethod "thawChildNotify" o = Gtk.Widget.WidgetThawChildNotifyMethodInfo
ResolveDockMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveDockMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
ResolveDockMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
ResolveDockMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
ResolveDockMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
ResolveDockMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
ResolveDockMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveDockMethod "unregisterWindow" o = Gtk.Widget.WidgetUnregisterWindowMethodInfo
ResolveDockMethod "unsetFocusChain" o = Gtk.Container.ContainerUnsetFocusChainMethodInfo
ResolveDockMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
ResolveDockMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveDockMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
ResolveDockMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
ResolveDockMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
ResolveDockMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
ResolveDockMethod "getAllocatedSize" o = Gtk.Widget.WidgetGetAllocatedSizeMethodInfo
ResolveDockMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
ResolveDockMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
ResolveDockMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
ResolveDockMethod "getAppPaintable" o = Gtk.Widget.WidgetGetAppPaintableMethodInfo
ResolveDockMethod "getBorderWidth" o = Gtk.Container.ContainerGetBorderWidthMethodInfo
ResolveDockMethod "getCanDefault" o = Gtk.Widget.WidgetGetCanDefaultMethodInfo
ResolveDockMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
ResolveDockMethod "getChildRequisition" o = Gtk.Widget.WidgetGetChildRequisitionMethodInfo
ResolveDockMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
ResolveDockMethod "getChildren" o = Gtk.Container.ContainerGetChildrenMethodInfo
ResolveDockMethod "getClip" o = Gtk.Widget.WidgetGetClipMethodInfo
ResolveDockMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
ResolveDockMethod "getCompositeName" o = Gtk.Widget.WidgetGetCompositeNameMethodInfo
ResolveDockMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveDockMethod "getDeviceEnabled" o = Gtk.Widget.WidgetGetDeviceEnabledMethodInfo
ResolveDockMethod "getDeviceEvents" o = Gtk.Widget.WidgetGetDeviceEventsMethodInfo
ResolveDockMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
ResolveDockMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
ResolveDockMethod "getDoubleBuffered" o = Gtk.Widget.WidgetGetDoubleBufferedMethodInfo
ResolveDockMethod "getEvents" o = Gtk.Widget.WidgetGetEventsMethodInfo
ResolveDockMethod "getFocusChain" o = Gtk.Container.ContainerGetFocusChainMethodInfo
ResolveDockMethod "getFocusChild" o = Gtk.Container.ContainerGetFocusChildMethodInfo
ResolveDockMethod "getFocusHadjustment" o = Gtk.Container.ContainerGetFocusHadjustmentMethodInfo
ResolveDockMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
ResolveDockMethod "getFocusVadjustment" o = Gtk.Container.ContainerGetFocusVadjustmentMethodInfo
ResolveDockMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
ResolveDockMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
ResolveDockMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
ResolveDockMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
ResolveDockMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
ResolveDockMethod "getHasWindow" o = Gtk.Widget.WidgetGetHasWindowMethodInfo
ResolveDockMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
ResolveDockMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
ResolveDockMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
ResolveDockMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
ResolveDockMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
ResolveDockMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
ResolveDockMethod "getMarginLeft" o = Gtk.Widget.WidgetGetMarginLeftMethodInfo
ResolveDockMethod "getMarginRight" o = Gtk.Widget.WidgetGetMarginRightMethodInfo
ResolveDockMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
ResolveDockMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
ResolveDockMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
ResolveDockMethod "getModifierStyle" o = Gtk.Widget.WidgetGetModifierStyleMethodInfo
ResolveDockMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
ResolveDockMethod "getNoShowAll" o = Gtk.Widget.WidgetGetNoShowAllMethodInfo
ResolveDockMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
ResolveDockMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
ResolveDockMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
ResolveDockMethod "getParentWindow" o = Gtk.Widget.WidgetGetParentWindowMethodInfo
ResolveDockMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
ResolveDockMethod "getPathForChild" o = Gtk.Container.ContainerGetPathForChildMethodInfo
ResolveDockMethod "getPointer" o = Gtk.Widget.WidgetGetPointerMethodInfo
ResolveDockMethod "getPreferredHeight" o = Gtk.Widget.WidgetGetPreferredHeightMethodInfo
ResolveDockMethod "getPreferredHeightAndBaselineForWidth" o = Gtk.Widget.WidgetGetPreferredHeightAndBaselineForWidthMethodInfo
ResolveDockMethod "getPreferredHeightForWidth" o = Gtk.Widget.WidgetGetPreferredHeightForWidthMethodInfo
ResolveDockMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
ResolveDockMethod "getPreferredWidth" o = Gtk.Widget.WidgetGetPreferredWidthMethodInfo
ResolveDockMethod "getPreferredWidthForHeight" o = Gtk.Widget.WidgetGetPreferredWidthForHeightMethodInfo
ResolveDockMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveDockMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveDockMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
ResolveDockMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
ResolveDockMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
ResolveDockMethod "getRequisition" o = Gtk.Widget.WidgetGetRequisitionMethodInfo
ResolveDockMethod "getResizeMode" o = Gtk.Container.ContainerGetResizeModeMethodInfo
ResolveDockMethod "getRootWindow" o = Gtk.Widget.WidgetGetRootWindowMethodInfo
ResolveDockMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
ResolveDockMethod "getScreen" o = Gtk.Widget.WidgetGetScreenMethodInfo
ResolveDockMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
ResolveDockMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
ResolveDockMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
ResolveDockMethod "getState" o = Gtk.Widget.WidgetGetStateMethodInfo
ResolveDockMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
ResolveDockMethod "getStyle" o = Gtk.Widget.WidgetGetStyleMethodInfo
ResolveDockMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
ResolveDockMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
ResolveDockMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
ResolveDockMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
ResolveDockMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
ResolveDockMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
ResolveDockMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
ResolveDockMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
ResolveDockMethod "getValignWithBaseline" o = Gtk.Widget.WidgetGetValignWithBaselineMethodInfo
ResolveDockMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
ResolveDockMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
ResolveDockMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
ResolveDockMethod "getVisual" o = Gtk.Widget.WidgetGetVisualMethodInfo
ResolveDockMethod "getWindow" o = Gtk.Widget.WidgetGetWindowMethodInfo
ResolveDockMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
ResolveDockMethod "setAllocation" o = Gtk.Widget.WidgetSetAllocationMethodInfo
ResolveDockMethod "setAppPaintable" o = Gtk.Widget.WidgetSetAppPaintableMethodInfo
ResolveDockMethod "setBorderWidth" o = Gtk.Container.ContainerSetBorderWidthMethodInfo
ResolveDockMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
ResolveDockMethod "setCanDefault" o = Gtk.Widget.WidgetSetCanDefaultMethodInfo
ResolveDockMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
ResolveDockMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
ResolveDockMethod "setClip" o = Gtk.Widget.WidgetSetClipMethodInfo
ResolveDockMethod "setCompositeName" o = Gtk.Widget.WidgetSetCompositeNameMethodInfo
ResolveDockMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveDockMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveDockMethod "setDeviceEnabled" o = Gtk.Widget.WidgetSetDeviceEnabledMethodInfo
ResolveDockMethod "setDeviceEvents" o = Gtk.Widget.WidgetSetDeviceEventsMethodInfo
ResolveDockMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
ResolveDockMethod "setDoubleBuffered" o = Gtk.Widget.WidgetSetDoubleBufferedMethodInfo
ResolveDockMethod "setEvents" o = Gtk.Widget.WidgetSetEventsMethodInfo
ResolveDockMethod "setFocusChain" o = Gtk.Container.ContainerSetFocusChainMethodInfo
ResolveDockMethod "setFocusChild" o = Gtk.Container.ContainerSetFocusChildMethodInfo
ResolveDockMethod "setFocusHadjustment" o = Gtk.Container.ContainerSetFocusHadjustmentMethodInfo
ResolveDockMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
ResolveDockMethod "setFocusVadjustment" o = Gtk.Container.ContainerSetFocusVadjustmentMethodInfo
ResolveDockMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
ResolveDockMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
ResolveDockMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
ResolveDockMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
ResolveDockMethod "setHasWindow" o = Gtk.Widget.WidgetSetHasWindowMethodInfo
ResolveDockMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
ResolveDockMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
ResolveDockMethod "setMapped" o = Gtk.Widget.WidgetSetMappedMethodInfo
ResolveDockMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
ResolveDockMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
ResolveDockMethod "setMarginLeft" o = Gtk.Widget.WidgetSetMarginLeftMethodInfo
ResolveDockMethod "setMarginRight" o = Gtk.Widget.WidgetSetMarginRightMethodInfo
ResolveDockMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
ResolveDockMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
ResolveDockMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
ResolveDockMethod "setNoShowAll" o = Gtk.Widget.WidgetSetNoShowAllMethodInfo
ResolveDockMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
ResolveDockMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
ResolveDockMethod "setParentWindow" o = Gtk.Widget.WidgetSetParentWindowMethodInfo
ResolveDockMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveDockMethod "setRealized" o = Gtk.Widget.WidgetSetRealizedMethodInfo
ResolveDockMethod "setReallocateRedraws" o = Gtk.Container.ContainerSetReallocateRedrawsMethodInfo
ResolveDockMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
ResolveDockMethod "setRedrawOnAllocate" o = Gtk.Widget.WidgetSetRedrawOnAllocateMethodInfo
ResolveDockMethod "setResizeMode" o = Gtk.Container.ContainerSetResizeModeMethodInfo
ResolveDockMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
ResolveDockMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
ResolveDockMethod "setState" o = Gtk.Widget.WidgetSetStateMethodInfo
ResolveDockMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
ResolveDockMethod "setStyle" o = Gtk.Widget.WidgetSetStyleMethodInfo
ResolveDockMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
ResolveDockMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
ResolveDockMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
ResolveDockMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
ResolveDockMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
ResolveDockMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
ResolveDockMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
ResolveDockMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
ResolveDockMethod "setVisual" o = Gtk.Widget.WidgetSetVisualMethodInfo
ResolveDockMethod "setWindow" o = Gtk.Widget.WidgetSetWindowMethodInfo
ResolveDockMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveDockMethod t Dock, O.OverloadedMethod info Dock p) => OL.IsLabel t (Dock -> 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 ~ ResolveDockMethod t Dock, O.OverloadedMethod info Dock p, R.HasField t Dock p) => R.HasField t Dock p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveDockMethod t Dock, O.OverloadedMethodInfo info Dock) => OL.IsLabel t (O.MethodProxy info Dock) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Dock = DockSignalList
type DockSignalList = ('[ '("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), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mapEvent", Gtk.Widget.WidgetMapEventSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("motionNotifyEvent", Gtk.Widget.WidgetMotionNotifyEventSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("parentSet", Gtk.Widget.WidgetParentSetSignalInfo), '("popupMenu", Gtk.Widget.WidgetPopupMenuSignalInfo), '("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