{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Dazzle.Objects.DockOverlay
(
DockOverlay(..) ,
IsDockOverlay ,
toDockOverlay ,
#if defined(ENABLE_OVERLOADING)
ResolveDockOverlayMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DockOverlayGetEdgeMethodInfo ,
#endif
dockOverlayGetEdge ,
#if defined(ENABLE_OVERLOADING)
DockOverlayGetEdgeAdjustmentMethodInfo ,
#endif
dockOverlayGetEdgeAdjustment ,
dockOverlayNew ,
DockOverlayHideEdgesCallback ,
#if defined(ENABLE_OVERLOADING)
DockOverlayHideEdgesSignalInfo ,
#endif
afterDockOverlayHideEdges ,
onDockOverlayHideEdges ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import {-# SOURCE #-} qualified GI.Dazzle.Interfaces.Dock as Dazzle.Dock
import {-# SOURCE #-} qualified GI.Dazzle.Interfaces.DockItem as Dazzle.DockItem
import {-# SOURCE #-} qualified GI.Dazzle.Objects.Bin as Dazzle.Bin
import {-# SOURCE #-} qualified GI.Dazzle.Objects.DockManager as Dazzle.DockManager
import {-# SOURCE #-} qualified GI.Dazzle.Objects.DockOverlayEdge as Dazzle.DockOverlayEdge
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.Adjustment as Gtk.Adjustment
import qualified GI.Gtk.Objects.Bin as Gtk.Bin
import qualified GI.Gtk.Objects.Container as Gtk.Container
import qualified GI.Gtk.Objects.EventBox as Gtk.EventBox
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 {-# SOURCE #-} qualified GI.Dazzle.Objects.DockOverlayEdge as Dazzle.DockOverlayEdge
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Enums as Gtk.Enums
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Objects.Adjustment as Gtk.Adjustment
import qualified GI.Gtk.Objects.Bin as Gtk.Bin
import qualified GI.Gtk.Objects.Container as Gtk.Container
import qualified GI.Gtk.Objects.EventBox as Gtk.EventBox
import qualified GI.Gtk.Objects.Widget as Gtk.Widget
#endif
newtype DockOverlay = DockOverlay (SP.ManagedPtr DockOverlay)
deriving (DockOverlay -> DockOverlay -> Bool
(DockOverlay -> DockOverlay -> Bool)
-> (DockOverlay -> DockOverlay -> Bool) -> Eq DockOverlay
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DockOverlay -> DockOverlay -> Bool
== :: DockOverlay -> DockOverlay -> Bool
$c/= :: DockOverlay -> DockOverlay -> Bool
/= :: DockOverlay -> DockOverlay -> Bool
Eq)
instance SP.ManagedPtrNewtype DockOverlay where
toManagedPtr :: DockOverlay -> ManagedPtr DockOverlay
toManagedPtr (DockOverlay ManagedPtr DockOverlay
p) = ManagedPtr DockOverlay
p
foreign import ccall "dzl_dock_overlay_get_type"
c_dzl_dock_overlay_get_type :: IO B.Types.GType
instance B.Types.TypedObject DockOverlay where
glibType :: IO GType
glibType = IO GType
c_dzl_dock_overlay_get_type
instance B.Types.GObject DockOverlay
class (SP.GObject o, O.IsDescendantOf DockOverlay o) => IsDockOverlay o
instance (SP.GObject o, O.IsDescendantOf DockOverlay o) => IsDockOverlay o
instance O.HasParentTypes DockOverlay
type instance O.ParentTypes DockOverlay = '[Gtk.EventBox.EventBox, Gtk.Bin.Bin, Gtk.Container.Container, Gtk.Widget.Widget, GObject.Object.Object, Atk.ImplementorIface.ImplementorIface, Dazzle.Dock.Dock, Dazzle.DockItem.DockItem, Gtk.Buildable.Buildable]
toDockOverlay :: (MIO.MonadIO m, IsDockOverlay o) => o -> m DockOverlay
toDockOverlay :: forall (m :: * -> *) o.
(MonadIO m, IsDockOverlay o) =>
o -> m DockOverlay
toDockOverlay = IO DockOverlay -> m DockOverlay
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO DockOverlay -> m DockOverlay)
-> (o -> IO DockOverlay) -> o -> m DockOverlay
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DockOverlay -> DockOverlay) -> o -> IO DockOverlay
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr DockOverlay -> DockOverlay
DockOverlay
instance B.GValue.IsGValue (Maybe DockOverlay) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_dzl_dock_overlay_get_type
gvalueSet_ :: Ptr GValue -> Maybe DockOverlay -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DockOverlay
P.Nothing = Ptr GValue -> Ptr DockOverlay -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DockOverlay
forall a. Ptr a
FP.nullPtr :: FP.Ptr DockOverlay)
gvalueSet_ Ptr GValue
gv (P.Just DockOverlay
obj) = DockOverlay -> (Ptr DockOverlay -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DockOverlay
obj (Ptr GValue -> Ptr DockOverlay -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe DockOverlay)
gvalueGet_ Ptr GValue
gv = do
Ptr DockOverlay
ptr <- Ptr GValue -> IO (Ptr DockOverlay)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DockOverlay)
if Ptr DockOverlay
ptr Ptr DockOverlay -> Ptr DockOverlay -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DockOverlay
forall a. Ptr a
FP.nullPtr
then DockOverlay -> Maybe DockOverlay
forall a. a -> Maybe a
P.Just (DockOverlay -> Maybe DockOverlay)
-> IO DockOverlay -> IO (Maybe DockOverlay)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr DockOverlay -> DockOverlay)
-> Ptr DockOverlay -> IO DockOverlay
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DockOverlay -> DockOverlay
DockOverlay Ptr DockOverlay
ptr
else Maybe DockOverlay -> IO (Maybe DockOverlay)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DockOverlay
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveDockOverlayMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveDockOverlayMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
ResolveDockOverlayMethod "add" o = Gtk.Container.ContainerAddMethodInfo
ResolveDockOverlayMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
ResolveDockOverlayMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
ResolveDockOverlayMethod "addDeviceEvents" o = Gtk.Widget.WidgetAddDeviceEventsMethodInfo
ResolveDockOverlayMethod "addEvents" o = Gtk.Widget.WidgetAddEventsMethodInfo
ResolveDockOverlayMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
ResolveDockOverlayMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
ResolveDockOverlayMethod "adopt" o = Dazzle.DockItem.DockItemAdoptMethodInfo
ResolveDockOverlayMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveDockOverlayMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveDockOverlayMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
ResolveDockOverlayMethod "checkResize" o = Gtk.Container.ContainerCheckResizeMethodInfo
ResolveDockOverlayMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
ResolveDockOverlayMethod "childGetProperty" o = Gtk.Container.ContainerChildGetPropertyMethodInfo
ResolveDockOverlayMethod "childNotify" o = Gtk.Container.ContainerChildNotifyMethodInfo
ResolveDockOverlayMethod "childNotifyByPspec" o = Gtk.Container.ContainerChildNotifyByPspecMethodInfo
ResolveDockOverlayMethod "childSetProperty" o = Gtk.Container.ContainerChildSetPropertyMethodInfo
ResolveDockOverlayMethod "childType" o = Gtk.Container.ContainerChildTypeMethodInfo
ResolveDockOverlayMethod "classPath" o = Gtk.Widget.WidgetClassPathMethodInfo
ResolveDockOverlayMethod "close" o = Dazzle.DockItem.DockItemCloseMethodInfo
ResolveDockOverlayMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
ResolveDockOverlayMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
ResolveDockOverlayMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
ResolveDockOverlayMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
ResolveDockOverlayMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
ResolveDockOverlayMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
ResolveDockOverlayMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
ResolveDockOverlayMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
ResolveDockOverlayMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
ResolveDockOverlayMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
ResolveDockOverlayMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
ResolveDockOverlayMethod "dragBeginWithCoordinates" o = Gtk.Widget.WidgetDragBeginWithCoordinatesMethodInfo
ResolveDockOverlayMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
ResolveDockOverlayMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
ResolveDockOverlayMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
ResolveDockOverlayMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
ResolveDockOverlayMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
ResolveDockOverlayMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
ResolveDockOverlayMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
ResolveDockOverlayMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
ResolveDockOverlayMethod "dragDestSetProxy" o = Gtk.Widget.WidgetDragDestSetProxyMethodInfo
ResolveDockOverlayMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
ResolveDockOverlayMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
ResolveDockOverlayMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
ResolveDockOverlayMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
ResolveDockOverlayMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
ResolveDockOverlayMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
ResolveDockOverlayMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
ResolveDockOverlayMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
ResolveDockOverlayMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
ResolveDockOverlayMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
ResolveDockOverlayMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
ResolveDockOverlayMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
ResolveDockOverlayMethod "dragSourceSetIconPixbuf" o = Gtk.Widget.WidgetDragSourceSetIconPixbufMethodInfo
ResolveDockOverlayMethod "dragSourceSetIconStock" o = Gtk.Widget.WidgetDragSourceSetIconStockMethodInfo
ResolveDockOverlayMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
ResolveDockOverlayMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
ResolveDockOverlayMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
ResolveDockOverlayMethod "draw" o = Gtk.Widget.WidgetDrawMethodInfo
ResolveDockOverlayMethod "emitPresented" o = Dazzle.DockItem.DockItemEmitPresentedMethodInfo
ResolveDockOverlayMethod "ensureStyle" o = Gtk.Widget.WidgetEnsureStyleMethodInfo
ResolveDockOverlayMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
ResolveDockOverlayMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
ResolveDockOverlayMethod "forall" o = Gtk.Container.ContainerForallMethodInfo
ResolveDockOverlayMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveDockOverlayMethod "foreach" o = Gtk.Container.ContainerForeachMethodInfo
ResolveDockOverlayMethod "freezeChildNotify" o = Gtk.Widget.WidgetFreezeChildNotifyMethodInfo
ResolveDockOverlayMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveDockOverlayMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveDockOverlayMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
ResolveDockOverlayMethod "grabDefault" o = Gtk.Widget.WidgetGrabDefaultMethodInfo
ResolveDockOverlayMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
ResolveDockOverlayMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
ResolveDockOverlayMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
ResolveDockOverlayMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
ResolveDockOverlayMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
ResolveDockOverlayMethod "hasRcStyle" o = Gtk.Widget.WidgetHasRcStyleMethodInfo
ResolveDockOverlayMethod "hasScreen" o = Gtk.Widget.WidgetHasScreenMethodInfo
ResolveDockOverlayMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
ResolveDockOverlayMethod "hasWidgets" o = Dazzle.DockItem.DockItemHasWidgetsMethodInfo
ResolveDockOverlayMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
ResolveDockOverlayMethod "hideOnDelete" o = Gtk.Widget.WidgetHideOnDeleteMethodInfo
ResolveDockOverlayMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
ResolveDockOverlayMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
ResolveDockOverlayMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
ResolveDockOverlayMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
ResolveDockOverlayMethod "intersect" o = Gtk.Widget.WidgetIntersectMethodInfo
ResolveDockOverlayMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
ResolveDockOverlayMethod "isComposited" o = Gtk.Widget.WidgetIsCompositedMethodInfo
ResolveDockOverlayMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
ResolveDockOverlayMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveDockOverlayMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
ResolveDockOverlayMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
ResolveDockOverlayMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
ResolveDockOverlayMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
ResolveDockOverlayMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
ResolveDockOverlayMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
ResolveDockOverlayMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
ResolveDockOverlayMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
ResolveDockOverlayMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
ResolveDockOverlayMethod "minimize" o = Dazzle.DockItem.DockItemMinimizeMethodInfo
ResolveDockOverlayMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
ResolveDockOverlayMethod "modifyBase" o = Gtk.Widget.WidgetModifyBaseMethodInfo
ResolveDockOverlayMethod "modifyBg" o = Gtk.Widget.WidgetModifyBgMethodInfo
ResolveDockOverlayMethod "modifyCursor" o = Gtk.Widget.WidgetModifyCursorMethodInfo
ResolveDockOverlayMethod "modifyFg" o = Gtk.Widget.WidgetModifyFgMethodInfo
ResolveDockOverlayMethod "modifyFont" o = Gtk.Widget.WidgetModifyFontMethodInfo
ResolveDockOverlayMethod "modifyStyle" o = Gtk.Widget.WidgetModifyStyleMethodInfo
ResolveDockOverlayMethod "modifyText" o = Gtk.Widget.WidgetModifyTextMethodInfo
ResolveDockOverlayMethod "needsAttention" o = Dazzle.DockItem.DockItemNeedsAttentionMethodInfo
ResolveDockOverlayMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveDockOverlayMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveDockOverlayMethod "overrideBackgroundColor" o = Gtk.Widget.WidgetOverrideBackgroundColorMethodInfo
ResolveDockOverlayMethod "overrideColor" o = Gtk.Widget.WidgetOverrideColorMethodInfo
ResolveDockOverlayMethod "overrideCursor" o = Gtk.Widget.WidgetOverrideCursorMethodInfo
ResolveDockOverlayMethod "overrideFont" o = Gtk.Widget.WidgetOverrideFontMethodInfo
ResolveDockOverlayMethod "overrideSymbolicColor" o = Gtk.Widget.WidgetOverrideSymbolicColorMethodInfo
ResolveDockOverlayMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
ResolveDockOverlayMethod "path" o = Gtk.Widget.WidgetPathMethodInfo
ResolveDockOverlayMethod "present" o = Dazzle.DockItem.DockItemPresentMethodInfo
ResolveDockOverlayMethod "presentChild" o = Dazzle.DockItem.DockItemPresentChildMethodInfo
ResolveDockOverlayMethod "propagateDraw" o = Gtk.Container.ContainerPropagateDrawMethodInfo
ResolveDockOverlayMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
ResolveDockOverlayMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
ResolveDockOverlayMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
ResolveDockOverlayMethod "queueDrawArea" o = Gtk.Widget.WidgetQueueDrawAreaMethodInfo
ResolveDockOverlayMethod "queueDrawRegion" o = Gtk.Widget.WidgetQueueDrawRegionMethodInfo
ResolveDockOverlayMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
ResolveDockOverlayMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
ResolveDockOverlayMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
ResolveDockOverlayMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveDockOverlayMethod "refGicon" o = Dazzle.DockItem.DockItemRefGiconMethodInfo
ResolveDockOverlayMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveDockOverlayMethod "regionIntersect" o = Gtk.Widget.WidgetRegionIntersectMethodInfo
ResolveDockOverlayMethod "registerWindow" o = Gtk.Widget.WidgetRegisterWindowMethodInfo
ResolveDockOverlayMethod "release" o = Dazzle.DockItem.DockItemReleaseMethodInfo
ResolveDockOverlayMethod "remove" o = Gtk.Container.ContainerRemoveMethodInfo
ResolveDockOverlayMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
ResolveDockOverlayMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
ResolveDockOverlayMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
ResolveDockOverlayMethod "renderIcon" o = Gtk.Widget.WidgetRenderIconMethodInfo
ResolveDockOverlayMethod "renderIconPixbuf" o = Gtk.Widget.WidgetRenderIconPixbufMethodInfo
ResolveDockOverlayMethod "reparent" o = Gtk.Widget.WidgetReparentMethodInfo
ResolveDockOverlayMethod "resetRcStyles" o = Gtk.Widget.WidgetResetRcStylesMethodInfo
ResolveDockOverlayMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
ResolveDockOverlayMethod "resizeChildren" o = Gtk.Container.ContainerResizeChildrenMethodInfo
ResolveDockOverlayMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveDockOverlayMethod "sendExpose" o = Gtk.Widget.WidgetSendExposeMethodInfo
ResolveDockOverlayMethod "sendFocusChange" o = Gtk.Widget.WidgetSendFocusChangeMethodInfo
ResolveDockOverlayMethod "shapeCombineRegion" o = Gtk.Widget.WidgetShapeCombineRegionMethodInfo
ResolveDockOverlayMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
ResolveDockOverlayMethod "showAll" o = Gtk.Widget.WidgetShowAllMethodInfo
ResolveDockOverlayMethod "showNow" o = Gtk.Widget.WidgetShowNowMethodInfo
ResolveDockOverlayMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
ResolveDockOverlayMethod "sizeAllocateWithBaseline" o = Gtk.Widget.WidgetSizeAllocateWithBaselineMethodInfo
ResolveDockOverlayMethod "sizeRequest" o = Gtk.Widget.WidgetSizeRequestMethodInfo
ResolveDockOverlayMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveDockOverlayMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveDockOverlayMethod "styleAttach" o = Gtk.Widget.WidgetStyleAttachMethodInfo
ResolveDockOverlayMethod "styleGetProperty" o = Gtk.Widget.WidgetStyleGetPropertyMethodInfo
ResolveDockOverlayMethod "thawChildNotify" o = Gtk.Widget.WidgetThawChildNotifyMethodInfo
ResolveDockOverlayMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveDockOverlayMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
ResolveDockOverlayMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
ResolveDockOverlayMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
ResolveDockOverlayMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
ResolveDockOverlayMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
ResolveDockOverlayMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveDockOverlayMethod "unregisterWindow" o = Gtk.Widget.WidgetUnregisterWindowMethodInfo
ResolveDockOverlayMethod "unsetFocusChain" o = Gtk.Container.ContainerUnsetFocusChainMethodInfo
ResolveDockOverlayMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
ResolveDockOverlayMethod "updateVisibility" o = Dazzle.DockItem.DockItemUpdateVisibilityMethodInfo
ResolveDockOverlayMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveDockOverlayMethod "getAboveChild" o = Gtk.EventBox.EventBoxGetAboveChildMethodInfo
ResolveDockOverlayMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
ResolveDockOverlayMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
ResolveDockOverlayMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
ResolveDockOverlayMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
ResolveDockOverlayMethod "getAllocatedSize" o = Gtk.Widget.WidgetGetAllocatedSizeMethodInfo
ResolveDockOverlayMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
ResolveDockOverlayMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
ResolveDockOverlayMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
ResolveDockOverlayMethod "getAppPaintable" o = Gtk.Widget.WidgetGetAppPaintableMethodInfo
ResolveDockOverlayMethod "getBorderWidth" o = Gtk.Container.ContainerGetBorderWidthMethodInfo
ResolveDockOverlayMethod "getCanClose" o = Dazzle.DockItem.DockItemGetCanCloseMethodInfo
ResolveDockOverlayMethod "getCanDefault" o = Gtk.Widget.WidgetGetCanDefaultMethodInfo
ResolveDockOverlayMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
ResolveDockOverlayMethod "getCanMinimize" o = Dazzle.DockItem.DockItemGetCanMinimizeMethodInfo
ResolveDockOverlayMethod "getChild" o = Gtk.Bin.BinGetChildMethodInfo
ResolveDockOverlayMethod "getChildRequisition" o = Gtk.Widget.WidgetGetChildRequisitionMethodInfo
ResolveDockOverlayMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
ResolveDockOverlayMethod "getChildren" o = Gtk.Container.ContainerGetChildrenMethodInfo
ResolveDockOverlayMethod "getClip" o = Gtk.Widget.WidgetGetClipMethodInfo
ResolveDockOverlayMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
ResolveDockOverlayMethod "getCompositeName" o = Gtk.Widget.WidgetGetCompositeNameMethodInfo
ResolveDockOverlayMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveDockOverlayMethod "getDeviceEnabled" o = Gtk.Widget.WidgetGetDeviceEnabledMethodInfo
ResolveDockOverlayMethod "getDeviceEvents" o = Gtk.Widget.WidgetGetDeviceEventsMethodInfo
ResolveDockOverlayMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
ResolveDockOverlayMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
ResolveDockOverlayMethod "getDoubleBuffered" o = Gtk.Widget.WidgetGetDoubleBufferedMethodInfo
ResolveDockOverlayMethod "getEdge" o = DockOverlayGetEdgeMethodInfo
ResolveDockOverlayMethod "getEdgeAdjustment" o = DockOverlayGetEdgeAdjustmentMethodInfo
ResolveDockOverlayMethod "getEvents" o = Gtk.Widget.WidgetGetEventsMethodInfo
ResolveDockOverlayMethod "getFocusChain" o = Gtk.Container.ContainerGetFocusChainMethodInfo
ResolveDockOverlayMethod "getFocusChild" o = Gtk.Container.ContainerGetFocusChildMethodInfo
ResolveDockOverlayMethod "getFocusHadjustment" o = Gtk.Container.ContainerGetFocusHadjustmentMethodInfo
ResolveDockOverlayMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
ResolveDockOverlayMethod "getFocusVadjustment" o = Gtk.Container.ContainerGetFocusVadjustmentMethodInfo
ResolveDockOverlayMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
ResolveDockOverlayMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
ResolveDockOverlayMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
ResolveDockOverlayMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
ResolveDockOverlayMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
ResolveDockOverlayMethod "getHasWindow" o = Gtk.Widget.WidgetGetHasWindowMethodInfo
ResolveDockOverlayMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
ResolveDockOverlayMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
ResolveDockOverlayMethod "getIconName" o = Dazzle.DockItem.DockItemGetIconNameMethodInfo
ResolveDockOverlayMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
ResolveDockOverlayMethod "getManager" o = Dazzle.DockItem.DockItemGetManagerMethodInfo
ResolveDockOverlayMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
ResolveDockOverlayMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
ResolveDockOverlayMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
ResolveDockOverlayMethod "getMarginLeft" o = Gtk.Widget.WidgetGetMarginLeftMethodInfo
ResolveDockOverlayMethod "getMarginRight" o = Gtk.Widget.WidgetGetMarginRightMethodInfo
ResolveDockOverlayMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
ResolveDockOverlayMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
ResolveDockOverlayMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
ResolveDockOverlayMethod "getModifierStyle" o = Gtk.Widget.WidgetGetModifierStyleMethodInfo
ResolveDockOverlayMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
ResolveDockOverlayMethod "getNoShowAll" o = Gtk.Widget.WidgetGetNoShowAllMethodInfo
ResolveDockOverlayMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
ResolveDockOverlayMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
ResolveDockOverlayMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
ResolveDockOverlayMethod "getParentWindow" o = Gtk.Widget.WidgetGetParentWindowMethodInfo
ResolveDockOverlayMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
ResolveDockOverlayMethod "getPathForChild" o = Gtk.Container.ContainerGetPathForChildMethodInfo
ResolveDockOverlayMethod "getPointer" o = Gtk.Widget.WidgetGetPointerMethodInfo
ResolveDockOverlayMethod "getPreferredHeight" o = Gtk.Widget.WidgetGetPreferredHeightMethodInfo
ResolveDockOverlayMethod "getPreferredHeightAndBaselineForWidth" o = Gtk.Widget.WidgetGetPreferredHeightAndBaselineForWidthMethodInfo
ResolveDockOverlayMethod "getPreferredHeightForWidth" o = Gtk.Widget.WidgetGetPreferredHeightForWidthMethodInfo
ResolveDockOverlayMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
ResolveDockOverlayMethod "getPreferredWidth" o = Gtk.Widget.WidgetGetPreferredWidthMethodInfo
ResolveDockOverlayMethod "getPreferredWidthForHeight" o = Gtk.Widget.WidgetGetPreferredWidthForHeightMethodInfo
ResolveDockOverlayMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveDockOverlayMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveDockOverlayMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
ResolveDockOverlayMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
ResolveDockOverlayMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
ResolveDockOverlayMethod "getRequisition" o = Gtk.Widget.WidgetGetRequisitionMethodInfo
ResolveDockOverlayMethod "getResizeMode" o = Gtk.Container.ContainerGetResizeModeMethodInfo
ResolveDockOverlayMethod "getRootWindow" o = Gtk.Widget.WidgetGetRootWindowMethodInfo
ResolveDockOverlayMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
ResolveDockOverlayMethod "getScreen" o = Gtk.Widget.WidgetGetScreenMethodInfo
ResolveDockOverlayMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
ResolveDockOverlayMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
ResolveDockOverlayMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
ResolveDockOverlayMethod "getState" o = Gtk.Widget.WidgetGetStateMethodInfo
ResolveDockOverlayMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
ResolveDockOverlayMethod "getStyle" o = Gtk.Widget.WidgetGetStyleMethodInfo
ResolveDockOverlayMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
ResolveDockOverlayMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
ResolveDockOverlayMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
ResolveDockOverlayMethod "getTitle" o = Dazzle.DockItem.DockItemGetTitleMethodInfo
ResolveDockOverlayMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
ResolveDockOverlayMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
ResolveDockOverlayMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
ResolveDockOverlayMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
ResolveDockOverlayMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
ResolveDockOverlayMethod "getValignWithBaseline" o = Gtk.Widget.WidgetGetValignWithBaselineMethodInfo
ResolveDockOverlayMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
ResolveDockOverlayMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
ResolveDockOverlayMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
ResolveDockOverlayMethod "getVisibleWindow" o = Gtk.EventBox.EventBoxGetVisibleWindowMethodInfo
ResolveDockOverlayMethod "getVisual" o = Gtk.Widget.WidgetGetVisualMethodInfo
ResolveDockOverlayMethod "getWindow" o = Gtk.Widget.WidgetGetWindowMethodInfo
ResolveDockOverlayMethod "setAboveChild" o = Gtk.EventBox.EventBoxSetAboveChildMethodInfo
ResolveDockOverlayMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
ResolveDockOverlayMethod "setAllocation" o = Gtk.Widget.WidgetSetAllocationMethodInfo
ResolveDockOverlayMethod "setAppPaintable" o = Gtk.Widget.WidgetSetAppPaintableMethodInfo
ResolveDockOverlayMethod "setBorderWidth" o = Gtk.Container.ContainerSetBorderWidthMethodInfo
ResolveDockOverlayMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
ResolveDockOverlayMethod "setCanDefault" o = Gtk.Widget.WidgetSetCanDefaultMethodInfo
ResolveDockOverlayMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
ResolveDockOverlayMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
ResolveDockOverlayMethod "setClip" o = Gtk.Widget.WidgetSetClipMethodInfo
ResolveDockOverlayMethod "setCompositeName" o = Gtk.Widget.WidgetSetCompositeNameMethodInfo
ResolveDockOverlayMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveDockOverlayMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveDockOverlayMethod "setDeviceEnabled" o = Gtk.Widget.WidgetSetDeviceEnabledMethodInfo
ResolveDockOverlayMethod "setDeviceEvents" o = Gtk.Widget.WidgetSetDeviceEventsMethodInfo
ResolveDockOverlayMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
ResolveDockOverlayMethod "setDoubleBuffered" o = Gtk.Widget.WidgetSetDoubleBufferedMethodInfo
ResolveDockOverlayMethod "setEvents" o = Gtk.Widget.WidgetSetEventsMethodInfo
ResolveDockOverlayMethod "setFocusChain" o = Gtk.Container.ContainerSetFocusChainMethodInfo
ResolveDockOverlayMethod "setFocusChild" o = Gtk.Container.ContainerSetFocusChildMethodInfo
ResolveDockOverlayMethod "setFocusHadjustment" o = Gtk.Container.ContainerSetFocusHadjustmentMethodInfo
ResolveDockOverlayMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
ResolveDockOverlayMethod "setFocusVadjustment" o = Gtk.Container.ContainerSetFocusVadjustmentMethodInfo
ResolveDockOverlayMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
ResolveDockOverlayMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
ResolveDockOverlayMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
ResolveDockOverlayMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
ResolveDockOverlayMethod "setHasWindow" o = Gtk.Widget.WidgetSetHasWindowMethodInfo
ResolveDockOverlayMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
ResolveDockOverlayMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
ResolveDockOverlayMethod "setManager" o = Dazzle.DockItem.DockItemSetManagerMethodInfo
ResolveDockOverlayMethod "setMapped" o = Gtk.Widget.WidgetSetMappedMethodInfo
ResolveDockOverlayMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
ResolveDockOverlayMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
ResolveDockOverlayMethod "setMarginLeft" o = Gtk.Widget.WidgetSetMarginLeftMethodInfo
ResolveDockOverlayMethod "setMarginRight" o = Gtk.Widget.WidgetSetMarginRightMethodInfo
ResolveDockOverlayMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
ResolveDockOverlayMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
ResolveDockOverlayMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
ResolveDockOverlayMethod "setNoShowAll" o = Gtk.Widget.WidgetSetNoShowAllMethodInfo
ResolveDockOverlayMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
ResolveDockOverlayMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
ResolveDockOverlayMethod "setParentWindow" o = Gtk.Widget.WidgetSetParentWindowMethodInfo
ResolveDockOverlayMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveDockOverlayMethod "setRealized" o = Gtk.Widget.WidgetSetRealizedMethodInfo
ResolveDockOverlayMethod "setReallocateRedraws" o = Gtk.Container.ContainerSetReallocateRedrawsMethodInfo
ResolveDockOverlayMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
ResolveDockOverlayMethod "setRedrawOnAllocate" o = Gtk.Widget.WidgetSetRedrawOnAllocateMethodInfo
ResolveDockOverlayMethod "setResizeMode" o = Gtk.Container.ContainerSetResizeModeMethodInfo
ResolveDockOverlayMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
ResolveDockOverlayMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
ResolveDockOverlayMethod "setState" o = Gtk.Widget.WidgetSetStateMethodInfo
ResolveDockOverlayMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
ResolveDockOverlayMethod "setStyle" o = Gtk.Widget.WidgetSetStyleMethodInfo
ResolveDockOverlayMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
ResolveDockOverlayMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
ResolveDockOverlayMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
ResolveDockOverlayMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
ResolveDockOverlayMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
ResolveDockOverlayMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
ResolveDockOverlayMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
ResolveDockOverlayMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
ResolveDockOverlayMethod "setVisibleWindow" o = Gtk.EventBox.EventBoxSetVisibleWindowMethodInfo
ResolveDockOverlayMethod "setVisual" o = Gtk.Widget.WidgetSetVisualMethodInfo
ResolveDockOverlayMethod "setWindow" o = Gtk.Widget.WidgetSetWindowMethodInfo
ResolveDockOverlayMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveDockOverlayMethod t DockOverlay, O.OverloadedMethod info DockOverlay p) => OL.IsLabel t (DockOverlay -> 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 ~ ResolveDockOverlayMethod t DockOverlay, O.OverloadedMethod info DockOverlay p, R.HasField t DockOverlay p) => R.HasField t DockOverlay p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveDockOverlayMethod t DockOverlay, O.OverloadedMethodInfo info DockOverlay) => OL.IsLabel t (O.MethodProxy info DockOverlay) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
type DockOverlayHideEdgesCallback =
IO ()
type C_DockOverlayHideEdgesCallback =
Ptr DockOverlay ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DockOverlayHideEdgesCallback :: C_DockOverlayHideEdgesCallback -> IO (FunPtr C_DockOverlayHideEdgesCallback)
wrap_DockOverlayHideEdgesCallback ::
GObject a => (a -> DockOverlayHideEdgesCallback) ->
C_DockOverlayHideEdgesCallback
wrap_DockOverlayHideEdgesCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_DockOverlayHideEdgesCallback
wrap_DockOverlayHideEdgesCallback a -> IO ()
gi'cb Ptr DockOverlay
gi'selfPtr Ptr ()
_ = do
Ptr DockOverlay -> (DockOverlay -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr DockOverlay
gi'selfPtr ((DockOverlay -> IO ()) -> IO ())
-> (DockOverlay -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \DockOverlay
gi'self -> a -> IO ()
gi'cb (DockOverlay -> a
forall a b. Coercible a b => a -> b
Coerce.coerce DockOverlay
gi'self)
onDockOverlayHideEdges :: (IsDockOverlay a, MonadIO m) => a -> ((?self :: a) => DockOverlayHideEdgesCallback) -> m SignalHandlerId
onDockOverlayHideEdges :: forall a (m :: * -> *).
(IsDockOverlay a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onDockOverlayHideEdges a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_DockOverlayHideEdgesCallback
wrapped' = (a -> IO ()) -> C_DockOverlayHideEdgesCallback
forall a.
GObject a =>
(a -> IO ()) -> C_DockOverlayHideEdgesCallback
wrap_DockOverlayHideEdgesCallback a -> IO ()
wrapped
FunPtr C_DockOverlayHideEdgesCallback
wrapped'' <- C_DockOverlayHideEdgesCallback
-> IO (FunPtr C_DockOverlayHideEdgesCallback)
mk_DockOverlayHideEdgesCallback C_DockOverlayHideEdgesCallback
wrapped'
a
-> Text
-> FunPtr C_DockOverlayHideEdgesCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"hide-edges" FunPtr C_DockOverlayHideEdgesCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDockOverlayHideEdges :: (IsDockOverlay a, MonadIO m) => a -> ((?self :: a) => DockOverlayHideEdgesCallback) -> m SignalHandlerId
afterDockOverlayHideEdges :: forall a (m :: * -> *).
(IsDockOverlay a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterDockOverlayHideEdges a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_DockOverlayHideEdgesCallback
wrapped' = (a -> IO ()) -> C_DockOverlayHideEdgesCallback
forall a.
GObject a =>
(a -> IO ()) -> C_DockOverlayHideEdgesCallback
wrap_DockOverlayHideEdgesCallback a -> IO ()
wrapped
FunPtr C_DockOverlayHideEdgesCallback
wrapped'' <- C_DockOverlayHideEdgesCallback
-> IO (FunPtr C_DockOverlayHideEdgesCallback)
mk_DockOverlayHideEdgesCallback C_DockOverlayHideEdgesCallback
wrapped'
a
-> Text
-> FunPtr C_DockOverlayHideEdgesCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"hide-edges" FunPtr C_DockOverlayHideEdgesCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data DockOverlayHideEdgesSignalInfo
instance SignalInfo DockOverlayHideEdgesSignalInfo where
type HaskellCallbackType DockOverlayHideEdgesSignalInfo = DockOverlayHideEdgesCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_DockOverlayHideEdgesCallback cb
cb'' <- mk_DockOverlayHideEdgesCallback cb'
connectSignalFunPtr obj "hide-edges" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockOverlay::hide-edges"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockOverlay.html#g:signal:hideEdges"})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DockOverlay
type instance O.AttributeList DockOverlay = DockOverlayAttributeList
type DockOverlayAttributeList = ('[ '("aboveChild", Gtk.EventBox.EventBoxAboveChildPropertyInfo), '("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", 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), '("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), '("visibleWindow", Gtk.EventBox.EventBoxVisibleWindowPropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo), '("window", Gtk.Widget.WidgetWindowPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DockOverlay = DockOverlaySignalList
type DockOverlaySignalList = ('[ '("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), '("hideEdges", DockOverlayHideEdgesSignalInfo), '("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_overlay_new" dzl_dock_overlay_new ::
IO (Ptr DockOverlay)
dockOverlayNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m DockOverlay
dockOverlayNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m DockOverlay
dockOverlayNew = IO DockOverlay -> m DockOverlay
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DockOverlay -> m DockOverlay)
-> IO DockOverlay -> m DockOverlay
forall a b. (a -> b) -> a -> b
$ do
Ptr DockOverlay
result <- IO (Ptr DockOverlay)
dzl_dock_overlay_new
Text -> Ptr DockOverlay -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dockOverlayNew" Ptr DockOverlay
result
DockOverlay
result' <- ((ManagedPtr DockOverlay -> DockOverlay)
-> Ptr DockOverlay -> IO DockOverlay
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DockOverlay -> DockOverlay
DockOverlay) Ptr DockOverlay
result
DockOverlay -> IO DockOverlay
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return DockOverlay
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "dzl_dock_overlay_get_edge" dzl_dock_overlay_get_edge ::
Ptr DockOverlay ->
CUInt ->
IO (Ptr Dazzle.DockOverlayEdge.DockOverlayEdge)
dockOverlayGetEdge ::
(B.CallStack.HasCallStack, MonadIO m, IsDockOverlay a) =>
a
-> Gtk.Enums.PositionType
-> m Dazzle.DockOverlayEdge.DockOverlayEdge
dockOverlayGetEdge :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDockOverlay a) =>
a -> PositionType -> m DockOverlayEdge
dockOverlayGetEdge a
self PositionType
position = IO DockOverlayEdge -> m DockOverlayEdge
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DockOverlayEdge -> m DockOverlayEdge)
-> IO DockOverlayEdge -> m DockOverlayEdge
forall a b. (a -> b) -> a -> b
$ do
Ptr DockOverlay
self' <- a -> IO (Ptr DockOverlay)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
let position' :: CUInt
position' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (PositionType -> Int) -> PositionType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PositionType -> Int
forall a. Enum a => a -> Int
fromEnum) PositionType
position
Ptr DockOverlayEdge
result <- Ptr DockOverlay -> CUInt -> IO (Ptr DockOverlayEdge)
dzl_dock_overlay_get_edge Ptr DockOverlay
self' CUInt
position'
Text -> Ptr DockOverlayEdge -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dockOverlayGetEdge" Ptr DockOverlayEdge
result
DockOverlayEdge
result' <- ((ManagedPtr DockOverlayEdge -> DockOverlayEdge)
-> Ptr DockOverlayEdge -> IO DockOverlayEdge
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DockOverlayEdge -> DockOverlayEdge
Dazzle.DockOverlayEdge.DockOverlayEdge) Ptr DockOverlayEdge
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
DockOverlayEdge -> IO DockOverlayEdge
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return DockOverlayEdge
result'
#if defined(ENABLE_OVERLOADING)
data DockOverlayGetEdgeMethodInfo
instance (signature ~ (Gtk.Enums.PositionType -> m Dazzle.DockOverlayEdge.DockOverlayEdge), MonadIO m, IsDockOverlay a) => O.OverloadedMethod DockOverlayGetEdgeMethodInfo a signature where
overloadedMethod = dockOverlayGetEdge
instance O.OverloadedMethodInfo DockOverlayGetEdgeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockOverlay.dockOverlayGetEdge",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockOverlay.html#v:dockOverlayGetEdge"
})
#endif
foreign import ccall "dzl_dock_overlay_get_edge_adjustment" dzl_dock_overlay_get_edge_adjustment ::
Ptr DockOverlay ->
CUInt ->
IO (Ptr Gtk.Adjustment.Adjustment)
dockOverlayGetEdgeAdjustment ::
(B.CallStack.HasCallStack, MonadIO m, IsDockOverlay a) =>
a
-> Gtk.Enums.PositionType
-> m Gtk.Adjustment.Adjustment
dockOverlayGetEdgeAdjustment :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDockOverlay a) =>
a -> PositionType -> m Adjustment
dockOverlayGetEdgeAdjustment a
self PositionType
position = IO Adjustment -> m Adjustment
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Adjustment -> m Adjustment) -> IO Adjustment -> m Adjustment
forall a b. (a -> b) -> a -> b
$ do
Ptr DockOverlay
self' <- a -> IO (Ptr DockOverlay)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
let position' :: CUInt
position' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (PositionType -> Int) -> PositionType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PositionType -> Int
forall a. Enum a => a -> Int
fromEnum) PositionType
position
Ptr Adjustment
result <- Ptr DockOverlay -> CUInt -> IO (Ptr Adjustment)
dzl_dock_overlay_get_edge_adjustment Ptr DockOverlay
self' CUInt
position'
Text -> Ptr Adjustment -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dockOverlayGetEdgeAdjustment" Ptr Adjustment
result
Adjustment
result' <- ((ManagedPtr Adjustment -> Adjustment)
-> Ptr Adjustment -> IO Adjustment
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Adjustment -> Adjustment
Gtk.Adjustment.Adjustment) Ptr Adjustment
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Adjustment -> IO Adjustment
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Adjustment
result'
#if defined(ENABLE_OVERLOADING)
data DockOverlayGetEdgeAdjustmentMethodInfo
instance (signature ~ (Gtk.Enums.PositionType -> m Gtk.Adjustment.Adjustment), MonadIO m, IsDockOverlay a) => O.OverloadedMethod DockOverlayGetEdgeAdjustmentMethodInfo a signature where
overloadedMethod = dockOverlayGetEdgeAdjustment
instance O.OverloadedMethodInfo DockOverlayGetEdgeAdjustmentMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockOverlay.dockOverlayGetEdgeAdjustment",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockOverlay.html#v:dockOverlayGetEdgeAdjustment"
})
#endif