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