{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Dazzle.Objects.DockRevealer
(
DockRevealer(..) ,
IsDockRevealer ,
toDockRevealer ,
#if defined(ENABLE_OVERLOADING)
ResolveDockRevealerMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DockRevealerAnimateToPositionMethodInfo ,
#endif
dockRevealerAnimateToPosition ,
#if defined(ENABLE_OVERLOADING)
DockRevealerGetChildRevealedMethodInfo ,
#endif
dockRevealerGetChildRevealed ,
#if defined(ENABLE_OVERLOADING)
DockRevealerGetPositionMethodInfo ,
#endif
dockRevealerGetPosition ,
#if defined(ENABLE_OVERLOADING)
DockRevealerGetPositionSetMethodInfo ,
#endif
dockRevealerGetPositionSet ,
#if defined(ENABLE_OVERLOADING)
DockRevealerGetRevealChildMethodInfo ,
#endif
dockRevealerGetRevealChild ,
#if defined(ENABLE_OVERLOADING)
DockRevealerGetTransitionDurationMethodInfo,
#endif
dockRevealerGetTransitionDuration ,
#if defined(ENABLE_OVERLOADING)
DockRevealerGetTransitionTypeMethodInfo ,
#endif
dockRevealerGetTransitionType ,
#if defined(ENABLE_OVERLOADING)
DockRevealerIsAnimatingMethodInfo ,
#endif
dockRevealerIsAnimating ,
dockRevealerNew ,
#if defined(ENABLE_OVERLOADING)
DockRevealerSetPositionMethodInfo ,
#endif
dockRevealerSetPosition ,
#if defined(ENABLE_OVERLOADING)
DockRevealerSetPositionSetMethodInfo ,
#endif
dockRevealerSetPositionSet ,
#if defined(ENABLE_OVERLOADING)
DockRevealerSetRevealChildMethodInfo ,
#endif
dockRevealerSetRevealChild ,
#if defined(ENABLE_OVERLOADING)
DockRevealerSetTransitionDurationMethodInfo,
#endif
dockRevealerSetTransitionDuration ,
#if defined(ENABLE_OVERLOADING)
DockRevealerSetTransitionTypeMethodInfo ,
#endif
dockRevealerSetTransitionType ,
#if defined(ENABLE_OVERLOADING)
DockRevealerChildRevealedPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
dockRevealerChildRevealed ,
#endif
getDockRevealerChildRevealed ,
#if defined(ENABLE_OVERLOADING)
DockRevealerPositionPropertyInfo ,
#endif
constructDockRevealerPosition ,
#if defined(ENABLE_OVERLOADING)
dockRevealerPosition ,
#endif
getDockRevealerPosition ,
setDockRevealerPosition ,
#if defined(ENABLE_OVERLOADING)
DockRevealerPositionSetPropertyInfo ,
#endif
constructDockRevealerPositionSet ,
#if defined(ENABLE_OVERLOADING)
dockRevealerPositionSet ,
#endif
getDockRevealerPositionSet ,
setDockRevealerPositionSet ,
#if defined(ENABLE_OVERLOADING)
DockRevealerRevealChildPropertyInfo ,
#endif
constructDockRevealerRevealChild ,
#if defined(ENABLE_OVERLOADING)
dockRevealerRevealChild ,
#endif
getDockRevealerRevealChild ,
setDockRevealerRevealChild ,
#if defined(ENABLE_OVERLOADING)
DockRevealerTransitionDurationPropertyInfo,
#endif
constructDockRevealerTransitionDuration ,
#if defined(ENABLE_OVERLOADING)
dockRevealerTransitionDuration ,
#endif
getDockRevealerTransitionDuration ,
setDockRevealerTransitionDuration ,
#if defined(ENABLE_OVERLOADING)
DockRevealerTransitionTypePropertyInfo ,
#endif
constructDockRevealerTransitionType ,
#if defined(ENABLE_OVERLOADING)
dockRevealerTransitionType ,
#endif
getDockRevealerTransitionType ,
setDockRevealerTransitionType ,
) 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.Enums as Dazzle.Enums
import {-# SOURCE #-} qualified GI.Dazzle.Objects.Bin as Dazzle.Bin
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Objects.Bin as Gtk.Bin
import qualified GI.Gtk.Objects.Container as Gtk.Container
import qualified GI.Gtk.Objects.Widget as Gtk.Widget
#else
import qualified GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import {-# SOURCE #-} qualified GI.Dazzle.Enums as Dazzle.Enums
import {-# SOURCE #-} qualified GI.Dazzle.Objects.Bin as Dazzle.Bin
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Objects.Bin as Gtk.Bin
import qualified GI.Gtk.Objects.Container as Gtk.Container
import qualified GI.Gtk.Objects.Widget as Gtk.Widget
#endif
newtype DockRevealer = DockRevealer (SP.ManagedPtr DockRevealer)
deriving (DockRevealer -> DockRevealer -> Bool
(DockRevealer -> DockRevealer -> Bool)
-> (DockRevealer -> DockRevealer -> Bool) -> Eq DockRevealer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DockRevealer -> DockRevealer -> Bool
== :: DockRevealer -> DockRevealer -> Bool
$c/= :: DockRevealer -> DockRevealer -> Bool
/= :: DockRevealer -> DockRevealer -> Bool
Eq)
instance SP.ManagedPtrNewtype DockRevealer where
toManagedPtr :: DockRevealer -> ManagedPtr DockRevealer
toManagedPtr (DockRevealer ManagedPtr DockRevealer
p) = ManagedPtr DockRevealer
p
foreign import ccall "dzl_dock_revealer_get_type"
c_dzl_dock_revealer_get_type :: IO B.Types.GType
instance B.Types.TypedObject DockRevealer where
glibType :: IO GType
glibType = IO GType
c_dzl_dock_revealer_get_type
instance B.Types.GObject DockRevealer
class (SP.GObject o, O.IsDescendantOf DockRevealer o) => IsDockRevealer o
instance (SP.GObject o, O.IsDescendantOf DockRevealer o) => IsDockRevealer o
instance O.HasParentTypes DockRevealer
type instance O.ParentTypes DockRevealer = '[Dazzle.Bin.Bin, Gtk.Bin.Bin, Gtk.Container.Container, Gtk.Widget.Widget, GObject.Object.Object, Atk.ImplementorIface.ImplementorIface, Gtk.Buildable.Buildable]
toDockRevealer :: (MIO.MonadIO m, IsDockRevealer o) => o -> m DockRevealer
toDockRevealer :: forall (m :: * -> *) o.
(MonadIO m, IsDockRevealer o) =>
o -> m DockRevealer
toDockRevealer = IO DockRevealer -> m DockRevealer
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO DockRevealer -> m DockRevealer)
-> (o -> IO DockRevealer) -> o -> m DockRevealer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DockRevealer -> DockRevealer) -> o -> IO DockRevealer
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr DockRevealer -> DockRevealer
DockRevealer
instance B.GValue.IsGValue (Maybe DockRevealer) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_dzl_dock_revealer_get_type
gvalueSet_ :: Ptr GValue -> Maybe DockRevealer -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DockRevealer
P.Nothing = Ptr GValue -> Ptr DockRevealer -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DockRevealer
forall a. Ptr a
FP.nullPtr :: FP.Ptr DockRevealer)
gvalueSet_ Ptr GValue
gv (P.Just DockRevealer
obj) = DockRevealer -> (Ptr DockRevealer -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DockRevealer
obj (Ptr GValue -> Ptr DockRevealer -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe DockRevealer)
gvalueGet_ Ptr GValue
gv = do
Ptr DockRevealer
ptr <- Ptr GValue -> IO (Ptr DockRevealer)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DockRevealer)
if Ptr DockRevealer
ptr Ptr DockRevealer -> Ptr DockRevealer -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DockRevealer
forall a. Ptr a
FP.nullPtr
then DockRevealer -> Maybe DockRevealer
forall a. a -> Maybe a
P.Just (DockRevealer -> Maybe DockRevealer)
-> IO DockRevealer -> IO (Maybe DockRevealer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr DockRevealer -> DockRevealer)
-> Ptr DockRevealer -> IO DockRevealer
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DockRevealer -> DockRevealer
DockRevealer Ptr DockRevealer
ptr
else Maybe DockRevealer -> IO (Maybe DockRevealer)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DockRevealer
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveDockRevealerMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveDockRevealerMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
ResolveDockRevealerMethod "add" o = Gtk.Container.ContainerAddMethodInfo
ResolveDockRevealerMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
ResolveDockRevealerMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
ResolveDockRevealerMethod "addDeviceEvents" o = Gtk.Widget.WidgetAddDeviceEventsMethodInfo
ResolveDockRevealerMethod "addEvents" o = Gtk.Widget.WidgetAddEventsMethodInfo
ResolveDockRevealerMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
ResolveDockRevealerMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
ResolveDockRevealerMethod "animateToPosition" o = DockRevealerAnimateToPositionMethodInfo
ResolveDockRevealerMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveDockRevealerMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveDockRevealerMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
ResolveDockRevealerMethod "checkResize" o = Gtk.Container.ContainerCheckResizeMethodInfo
ResolveDockRevealerMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
ResolveDockRevealerMethod "childGetProperty" o = Gtk.Container.ContainerChildGetPropertyMethodInfo
ResolveDockRevealerMethod "childNotify" o = Gtk.Container.ContainerChildNotifyMethodInfo
ResolveDockRevealerMethod "childNotifyByPspec" o = Gtk.Container.ContainerChildNotifyByPspecMethodInfo
ResolveDockRevealerMethod "childSetProperty" o = Gtk.Container.ContainerChildSetPropertyMethodInfo
ResolveDockRevealerMethod "childType" o = Gtk.Container.ContainerChildTypeMethodInfo
ResolveDockRevealerMethod "classPath" o = Gtk.Widget.WidgetClassPathMethodInfo
ResolveDockRevealerMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
ResolveDockRevealerMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
ResolveDockRevealerMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
ResolveDockRevealerMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
ResolveDockRevealerMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
ResolveDockRevealerMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
ResolveDockRevealerMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
ResolveDockRevealerMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
ResolveDockRevealerMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
ResolveDockRevealerMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
ResolveDockRevealerMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
ResolveDockRevealerMethod "dragBeginWithCoordinates" o = Gtk.Widget.WidgetDragBeginWithCoordinatesMethodInfo
ResolveDockRevealerMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
ResolveDockRevealerMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
ResolveDockRevealerMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
ResolveDockRevealerMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
ResolveDockRevealerMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
ResolveDockRevealerMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
ResolveDockRevealerMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
ResolveDockRevealerMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
ResolveDockRevealerMethod "dragDestSetProxy" o = Gtk.Widget.WidgetDragDestSetProxyMethodInfo
ResolveDockRevealerMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
ResolveDockRevealerMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
ResolveDockRevealerMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
ResolveDockRevealerMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
ResolveDockRevealerMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
ResolveDockRevealerMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
ResolveDockRevealerMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
ResolveDockRevealerMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
ResolveDockRevealerMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
ResolveDockRevealerMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
ResolveDockRevealerMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
ResolveDockRevealerMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
ResolveDockRevealerMethod "dragSourceSetIconPixbuf" o = Gtk.Widget.WidgetDragSourceSetIconPixbufMethodInfo
ResolveDockRevealerMethod "dragSourceSetIconStock" o = Gtk.Widget.WidgetDragSourceSetIconStockMethodInfo
ResolveDockRevealerMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
ResolveDockRevealerMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
ResolveDockRevealerMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
ResolveDockRevealerMethod "draw" o = Gtk.Widget.WidgetDrawMethodInfo
ResolveDockRevealerMethod "ensureStyle" o = Gtk.Widget.WidgetEnsureStyleMethodInfo
ResolveDockRevealerMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
ResolveDockRevealerMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
ResolveDockRevealerMethod "forall" o = Gtk.Container.ContainerForallMethodInfo
ResolveDockRevealerMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveDockRevealerMethod "foreach" o = Gtk.Container.ContainerForeachMethodInfo
ResolveDockRevealerMethod "freezeChildNotify" o = Gtk.Widget.WidgetFreezeChildNotifyMethodInfo
ResolveDockRevealerMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveDockRevealerMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveDockRevealerMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
ResolveDockRevealerMethod "grabDefault" o = Gtk.Widget.WidgetGrabDefaultMethodInfo
ResolveDockRevealerMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
ResolveDockRevealerMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
ResolveDockRevealerMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
ResolveDockRevealerMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
ResolveDockRevealerMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
ResolveDockRevealerMethod "hasRcStyle" o = Gtk.Widget.WidgetHasRcStyleMethodInfo
ResolveDockRevealerMethod "hasScreen" o = Gtk.Widget.WidgetHasScreenMethodInfo
ResolveDockRevealerMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
ResolveDockRevealerMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
ResolveDockRevealerMethod "hideOnDelete" o = Gtk.Widget.WidgetHideOnDeleteMethodInfo
ResolveDockRevealerMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
ResolveDockRevealerMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
ResolveDockRevealerMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
ResolveDockRevealerMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
ResolveDockRevealerMethod "intersect" o = Gtk.Widget.WidgetIntersectMethodInfo
ResolveDockRevealerMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
ResolveDockRevealerMethod "isAnimating" o = DockRevealerIsAnimatingMethodInfo
ResolveDockRevealerMethod "isComposited" o = Gtk.Widget.WidgetIsCompositedMethodInfo
ResolveDockRevealerMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
ResolveDockRevealerMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveDockRevealerMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
ResolveDockRevealerMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
ResolveDockRevealerMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
ResolveDockRevealerMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
ResolveDockRevealerMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
ResolveDockRevealerMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
ResolveDockRevealerMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
ResolveDockRevealerMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
ResolveDockRevealerMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
ResolveDockRevealerMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
ResolveDockRevealerMethod "modifyBase" o = Gtk.Widget.WidgetModifyBaseMethodInfo
ResolveDockRevealerMethod "modifyBg" o = Gtk.Widget.WidgetModifyBgMethodInfo
ResolveDockRevealerMethod "modifyCursor" o = Gtk.Widget.WidgetModifyCursorMethodInfo
ResolveDockRevealerMethod "modifyFg" o = Gtk.Widget.WidgetModifyFgMethodInfo
ResolveDockRevealerMethod "modifyFont" o = Gtk.Widget.WidgetModifyFontMethodInfo
ResolveDockRevealerMethod "modifyStyle" o = Gtk.Widget.WidgetModifyStyleMethodInfo
ResolveDockRevealerMethod "modifyText" o = Gtk.Widget.WidgetModifyTextMethodInfo
ResolveDockRevealerMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveDockRevealerMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveDockRevealerMethod "overrideBackgroundColor" o = Gtk.Widget.WidgetOverrideBackgroundColorMethodInfo
ResolveDockRevealerMethod "overrideColor" o = Gtk.Widget.WidgetOverrideColorMethodInfo
ResolveDockRevealerMethod "overrideCursor" o = Gtk.Widget.WidgetOverrideCursorMethodInfo
ResolveDockRevealerMethod "overrideFont" o = Gtk.Widget.WidgetOverrideFontMethodInfo
ResolveDockRevealerMethod "overrideSymbolicColor" o = Gtk.Widget.WidgetOverrideSymbolicColorMethodInfo
ResolveDockRevealerMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
ResolveDockRevealerMethod "path" o = Gtk.Widget.WidgetPathMethodInfo
ResolveDockRevealerMethod "propagateDraw" o = Gtk.Container.ContainerPropagateDrawMethodInfo
ResolveDockRevealerMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
ResolveDockRevealerMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
ResolveDockRevealerMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
ResolveDockRevealerMethod "queueDrawArea" o = Gtk.Widget.WidgetQueueDrawAreaMethodInfo
ResolveDockRevealerMethod "queueDrawRegion" o = Gtk.Widget.WidgetQueueDrawRegionMethodInfo
ResolveDockRevealerMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
ResolveDockRevealerMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
ResolveDockRevealerMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
ResolveDockRevealerMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveDockRevealerMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveDockRevealerMethod "regionIntersect" o = Gtk.Widget.WidgetRegionIntersectMethodInfo
ResolveDockRevealerMethod "registerWindow" o = Gtk.Widget.WidgetRegisterWindowMethodInfo
ResolveDockRevealerMethod "remove" o = Gtk.Container.ContainerRemoveMethodInfo
ResolveDockRevealerMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
ResolveDockRevealerMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
ResolveDockRevealerMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
ResolveDockRevealerMethod "renderIcon" o = Gtk.Widget.WidgetRenderIconMethodInfo
ResolveDockRevealerMethod "renderIconPixbuf" o = Gtk.Widget.WidgetRenderIconPixbufMethodInfo
ResolveDockRevealerMethod "reparent" o = Gtk.Widget.WidgetReparentMethodInfo
ResolveDockRevealerMethod "resetRcStyles" o = Gtk.Widget.WidgetResetRcStylesMethodInfo
ResolveDockRevealerMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
ResolveDockRevealerMethod "resizeChildren" o = Gtk.Container.ContainerResizeChildrenMethodInfo
ResolveDockRevealerMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveDockRevealerMethod "sendExpose" o = Gtk.Widget.WidgetSendExposeMethodInfo
ResolveDockRevealerMethod "sendFocusChange" o = Gtk.Widget.WidgetSendFocusChangeMethodInfo
ResolveDockRevealerMethod "shapeCombineRegion" o = Gtk.Widget.WidgetShapeCombineRegionMethodInfo
ResolveDockRevealerMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
ResolveDockRevealerMethod "showAll" o = Gtk.Widget.WidgetShowAllMethodInfo
ResolveDockRevealerMethod "showNow" o = Gtk.Widget.WidgetShowNowMethodInfo
ResolveDockRevealerMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
ResolveDockRevealerMethod "sizeAllocateWithBaseline" o = Gtk.Widget.WidgetSizeAllocateWithBaselineMethodInfo
ResolveDockRevealerMethod "sizeRequest" o = Gtk.Widget.WidgetSizeRequestMethodInfo
ResolveDockRevealerMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveDockRevealerMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveDockRevealerMethod "styleAttach" o = Gtk.Widget.WidgetStyleAttachMethodInfo
ResolveDockRevealerMethod "styleGetProperty" o = Gtk.Widget.WidgetStyleGetPropertyMethodInfo
ResolveDockRevealerMethod "thawChildNotify" o = Gtk.Widget.WidgetThawChildNotifyMethodInfo
ResolveDockRevealerMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveDockRevealerMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
ResolveDockRevealerMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
ResolveDockRevealerMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
ResolveDockRevealerMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
ResolveDockRevealerMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
ResolveDockRevealerMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveDockRevealerMethod "unregisterWindow" o = Gtk.Widget.WidgetUnregisterWindowMethodInfo
ResolveDockRevealerMethod "unsetFocusChain" o = Gtk.Container.ContainerUnsetFocusChainMethodInfo
ResolveDockRevealerMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
ResolveDockRevealerMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveDockRevealerMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
ResolveDockRevealerMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
ResolveDockRevealerMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
ResolveDockRevealerMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
ResolveDockRevealerMethod "getAllocatedSize" o = Gtk.Widget.WidgetGetAllocatedSizeMethodInfo
ResolveDockRevealerMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
ResolveDockRevealerMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
ResolveDockRevealerMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
ResolveDockRevealerMethod "getAppPaintable" o = Gtk.Widget.WidgetGetAppPaintableMethodInfo
ResolveDockRevealerMethod "getBorderWidth" o = Gtk.Container.ContainerGetBorderWidthMethodInfo
ResolveDockRevealerMethod "getCanDefault" o = Gtk.Widget.WidgetGetCanDefaultMethodInfo
ResolveDockRevealerMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
ResolveDockRevealerMethod "getChild" o = Gtk.Bin.BinGetChildMethodInfo
ResolveDockRevealerMethod "getChildRequisition" o = Gtk.Widget.WidgetGetChildRequisitionMethodInfo
ResolveDockRevealerMethod "getChildRevealed" o = DockRevealerGetChildRevealedMethodInfo
ResolveDockRevealerMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
ResolveDockRevealerMethod "getChildren" o = Gtk.Container.ContainerGetChildrenMethodInfo
ResolveDockRevealerMethod "getClip" o = Gtk.Widget.WidgetGetClipMethodInfo
ResolveDockRevealerMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
ResolveDockRevealerMethod "getCompositeName" o = Gtk.Widget.WidgetGetCompositeNameMethodInfo
ResolveDockRevealerMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveDockRevealerMethod "getDeviceEnabled" o = Gtk.Widget.WidgetGetDeviceEnabledMethodInfo
ResolveDockRevealerMethod "getDeviceEvents" o = Gtk.Widget.WidgetGetDeviceEventsMethodInfo
ResolveDockRevealerMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
ResolveDockRevealerMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
ResolveDockRevealerMethod "getDoubleBuffered" o = Gtk.Widget.WidgetGetDoubleBufferedMethodInfo
ResolveDockRevealerMethod "getEvents" o = Gtk.Widget.WidgetGetEventsMethodInfo
ResolveDockRevealerMethod "getFocusChain" o = Gtk.Container.ContainerGetFocusChainMethodInfo
ResolveDockRevealerMethod "getFocusChild" o = Gtk.Container.ContainerGetFocusChildMethodInfo
ResolveDockRevealerMethod "getFocusHadjustment" o = Gtk.Container.ContainerGetFocusHadjustmentMethodInfo
ResolveDockRevealerMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
ResolveDockRevealerMethod "getFocusVadjustment" o = Gtk.Container.ContainerGetFocusVadjustmentMethodInfo
ResolveDockRevealerMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
ResolveDockRevealerMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
ResolveDockRevealerMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
ResolveDockRevealerMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
ResolveDockRevealerMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
ResolveDockRevealerMethod "getHasWindow" o = Gtk.Widget.WidgetGetHasWindowMethodInfo
ResolveDockRevealerMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
ResolveDockRevealerMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
ResolveDockRevealerMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
ResolveDockRevealerMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
ResolveDockRevealerMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
ResolveDockRevealerMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
ResolveDockRevealerMethod "getMarginLeft" o = Gtk.Widget.WidgetGetMarginLeftMethodInfo
ResolveDockRevealerMethod "getMarginRight" o = Gtk.Widget.WidgetGetMarginRightMethodInfo
ResolveDockRevealerMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
ResolveDockRevealerMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
ResolveDockRevealerMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
ResolveDockRevealerMethod "getModifierStyle" o = Gtk.Widget.WidgetGetModifierStyleMethodInfo
ResolveDockRevealerMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
ResolveDockRevealerMethod "getNoShowAll" o = Gtk.Widget.WidgetGetNoShowAllMethodInfo
ResolveDockRevealerMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
ResolveDockRevealerMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
ResolveDockRevealerMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
ResolveDockRevealerMethod "getParentWindow" o = Gtk.Widget.WidgetGetParentWindowMethodInfo
ResolveDockRevealerMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
ResolveDockRevealerMethod "getPathForChild" o = Gtk.Container.ContainerGetPathForChildMethodInfo
ResolveDockRevealerMethod "getPointer" o = Gtk.Widget.WidgetGetPointerMethodInfo
ResolveDockRevealerMethod "getPosition" o = DockRevealerGetPositionMethodInfo
ResolveDockRevealerMethod "getPositionSet" o = DockRevealerGetPositionSetMethodInfo
ResolveDockRevealerMethod "getPreferredHeight" o = Gtk.Widget.WidgetGetPreferredHeightMethodInfo
ResolveDockRevealerMethod "getPreferredHeightAndBaselineForWidth" o = Gtk.Widget.WidgetGetPreferredHeightAndBaselineForWidthMethodInfo
ResolveDockRevealerMethod "getPreferredHeightForWidth" o = Gtk.Widget.WidgetGetPreferredHeightForWidthMethodInfo
ResolveDockRevealerMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
ResolveDockRevealerMethod "getPreferredWidth" o = Gtk.Widget.WidgetGetPreferredWidthMethodInfo
ResolveDockRevealerMethod "getPreferredWidthForHeight" o = Gtk.Widget.WidgetGetPreferredWidthForHeightMethodInfo
ResolveDockRevealerMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveDockRevealerMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveDockRevealerMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
ResolveDockRevealerMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
ResolveDockRevealerMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
ResolveDockRevealerMethod "getRequisition" o = Gtk.Widget.WidgetGetRequisitionMethodInfo
ResolveDockRevealerMethod "getResizeMode" o = Gtk.Container.ContainerGetResizeModeMethodInfo
ResolveDockRevealerMethod "getRevealChild" o = DockRevealerGetRevealChildMethodInfo
ResolveDockRevealerMethod "getRootWindow" o = Gtk.Widget.WidgetGetRootWindowMethodInfo
ResolveDockRevealerMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
ResolveDockRevealerMethod "getScreen" o = Gtk.Widget.WidgetGetScreenMethodInfo
ResolveDockRevealerMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
ResolveDockRevealerMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
ResolveDockRevealerMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
ResolveDockRevealerMethod "getState" o = Gtk.Widget.WidgetGetStateMethodInfo
ResolveDockRevealerMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
ResolveDockRevealerMethod "getStyle" o = Gtk.Widget.WidgetGetStyleMethodInfo
ResolveDockRevealerMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
ResolveDockRevealerMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
ResolveDockRevealerMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
ResolveDockRevealerMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
ResolveDockRevealerMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
ResolveDockRevealerMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
ResolveDockRevealerMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
ResolveDockRevealerMethod "getTransitionDuration" o = DockRevealerGetTransitionDurationMethodInfo
ResolveDockRevealerMethod "getTransitionType" o = DockRevealerGetTransitionTypeMethodInfo
ResolveDockRevealerMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
ResolveDockRevealerMethod "getValignWithBaseline" o = Gtk.Widget.WidgetGetValignWithBaselineMethodInfo
ResolveDockRevealerMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
ResolveDockRevealerMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
ResolveDockRevealerMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
ResolveDockRevealerMethod "getVisual" o = Gtk.Widget.WidgetGetVisualMethodInfo
ResolveDockRevealerMethod "getWindow" o = Gtk.Widget.WidgetGetWindowMethodInfo
ResolveDockRevealerMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
ResolveDockRevealerMethod "setAllocation" o = Gtk.Widget.WidgetSetAllocationMethodInfo
ResolveDockRevealerMethod "setAppPaintable" o = Gtk.Widget.WidgetSetAppPaintableMethodInfo
ResolveDockRevealerMethod "setBorderWidth" o = Gtk.Container.ContainerSetBorderWidthMethodInfo
ResolveDockRevealerMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
ResolveDockRevealerMethod "setCanDefault" o = Gtk.Widget.WidgetSetCanDefaultMethodInfo
ResolveDockRevealerMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
ResolveDockRevealerMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
ResolveDockRevealerMethod "setClip" o = Gtk.Widget.WidgetSetClipMethodInfo
ResolveDockRevealerMethod "setCompositeName" o = Gtk.Widget.WidgetSetCompositeNameMethodInfo
ResolveDockRevealerMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveDockRevealerMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveDockRevealerMethod "setDeviceEnabled" o = Gtk.Widget.WidgetSetDeviceEnabledMethodInfo
ResolveDockRevealerMethod "setDeviceEvents" o = Gtk.Widget.WidgetSetDeviceEventsMethodInfo
ResolveDockRevealerMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
ResolveDockRevealerMethod "setDoubleBuffered" o = Gtk.Widget.WidgetSetDoubleBufferedMethodInfo
ResolveDockRevealerMethod "setEvents" o = Gtk.Widget.WidgetSetEventsMethodInfo
ResolveDockRevealerMethod "setFocusChain" o = Gtk.Container.ContainerSetFocusChainMethodInfo
ResolveDockRevealerMethod "setFocusChild" o = Gtk.Container.ContainerSetFocusChildMethodInfo
ResolveDockRevealerMethod "setFocusHadjustment" o = Gtk.Container.ContainerSetFocusHadjustmentMethodInfo
ResolveDockRevealerMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
ResolveDockRevealerMethod "setFocusVadjustment" o = Gtk.Container.ContainerSetFocusVadjustmentMethodInfo
ResolveDockRevealerMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
ResolveDockRevealerMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
ResolveDockRevealerMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
ResolveDockRevealerMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
ResolveDockRevealerMethod "setHasWindow" o = Gtk.Widget.WidgetSetHasWindowMethodInfo
ResolveDockRevealerMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
ResolveDockRevealerMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
ResolveDockRevealerMethod "setMapped" o = Gtk.Widget.WidgetSetMappedMethodInfo
ResolveDockRevealerMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
ResolveDockRevealerMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
ResolveDockRevealerMethod "setMarginLeft" o = Gtk.Widget.WidgetSetMarginLeftMethodInfo
ResolveDockRevealerMethod "setMarginRight" o = Gtk.Widget.WidgetSetMarginRightMethodInfo
ResolveDockRevealerMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
ResolveDockRevealerMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
ResolveDockRevealerMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
ResolveDockRevealerMethod "setNoShowAll" o = Gtk.Widget.WidgetSetNoShowAllMethodInfo
ResolveDockRevealerMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
ResolveDockRevealerMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
ResolveDockRevealerMethod "setParentWindow" o = Gtk.Widget.WidgetSetParentWindowMethodInfo
ResolveDockRevealerMethod "setPosition" o = DockRevealerSetPositionMethodInfo
ResolveDockRevealerMethod "setPositionSet" o = DockRevealerSetPositionSetMethodInfo
ResolveDockRevealerMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveDockRevealerMethod "setRealized" o = Gtk.Widget.WidgetSetRealizedMethodInfo
ResolveDockRevealerMethod "setReallocateRedraws" o = Gtk.Container.ContainerSetReallocateRedrawsMethodInfo
ResolveDockRevealerMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
ResolveDockRevealerMethod "setRedrawOnAllocate" o = Gtk.Widget.WidgetSetRedrawOnAllocateMethodInfo
ResolveDockRevealerMethod "setResizeMode" o = Gtk.Container.ContainerSetResizeModeMethodInfo
ResolveDockRevealerMethod "setRevealChild" o = DockRevealerSetRevealChildMethodInfo
ResolveDockRevealerMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
ResolveDockRevealerMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
ResolveDockRevealerMethod "setState" o = Gtk.Widget.WidgetSetStateMethodInfo
ResolveDockRevealerMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
ResolveDockRevealerMethod "setStyle" o = Gtk.Widget.WidgetSetStyleMethodInfo
ResolveDockRevealerMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
ResolveDockRevealerMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
ResolveDockRevealerMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
ResolveDockRevealerMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
ResolveDockRevealerMethod "setTransitionDuration" o = DockRevealerSetTransitionDurationMethodInfo
ResolveDockRevealerMethod "setTransitionType" o = DockRevealerSetTransitionTypeMethodInfo
ResolveDockRevealerMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
ResolveDockRevealerMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
ResolveDockRevealerMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
ResolveDockRevealerMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
ResolveDockRevealerMethod "setVisual" o = Gtk.Widget.WidgetSetVisualMethodInfo
ResolveDockRevealerMethod "setWindow" o = Gtk.Widget.WidgetSetWindowMethodInfo
ResolveDockRevealerMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveDockRevealerMethod t DockRevealer, O.OverloadedMethod info DockRevealer p) => OL.IsLabel t (DockRevealer -> 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 ~ ResolveDockRevealerMethod t DockRevealer, O.OverloadedMethod info DockRevealer p, R.HasField t DockRevealer p) => R.HasField t DockRevealer p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveDockRevealerMethod t DockRevealer, O.OverloadedMethodInfo info DockRevealer) => OL.IsLabel t (O.MethodProxy info DockRevealer) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
getDockRevealerChildRevealed :: (MonadIO m, IsDockRevealer o) => o -> m Bool
getDockRevealerChildRevealed :: forall (m :: * -> *) o.
(MonadIO m, IsDockRevealer o) =>
o -> m Bool
getDockRevealerChildRevealed 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
"child-revealed"
#if defined(ENABLE_OVERLOADING)
data DockRevealerChildRevealedPropertyInfo
instance AttrInfo DockRevealerChildRevealedPropertyInfo where
type AttrAllowedOps DockRevealerChildRevealedPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint DockRevealerChildRevealedPropertyInfo = IsDockRevealer
type AttrSetTypeConstraint DockRevealerChildRevealedPropertyInfo = (~) ()
type AttrTransferTypeConstraint DockRevealerChildRevealedPropertyInfo = (~) ()
type AttrTransferType DockRevealerChildRevealedPropertyInfo = ()
type AttrGetType DockRevealerChildRevealedPropertyInfo = Bool
type AttrLabel DockRevealerChildRevealedPropertyInfo = "child-revealed"
type AttrOrigin DockRevealerChildRevealedPropertyInfo = DockRevealer
attrGet = getDockRevealerChildRevealed
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockRevealer.childRevealed"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockRevealer.html#g:attr:childRevealed"
})
#endif
getDockRevealerPosition :: (MonadIO m, IsDockRevealer o) => o -> m Int32
getDockRevealerPosition :: forall (m :: * -> *) o.
(MonadIO m, IsDockRevealer o) =>
o -> m Int32
getDockRevealerPosition o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"position"
setDockRevealerPosition :: (MonadIO m, IsDockRevealer o) => o -> Int32 -> m ()
setDockRevealerPosition :: forall (m :: * -> *) o.
(MonadIO m, IsDockRevealer o) =>
o -> Int32 -> m ()
setDockRevealerPosition o
obj Int32
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 -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"position" Int32
val
constructDockRevealerPosition :: (IsDockRevealer o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructDockRevealerPosition :: forall o (m :: * -> *).
(IsDockRevealer o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructDockRevealerPosition Int32
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 -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"position" Int32
val
#if defined(ENABLE_OVERLOADING)
data DockRevealerPositionPropertyInfo
instance AttrInfo DockRevealerPositionPropertyInfo where
type AttrAllowedOps DockRevealerPositionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint DockRevealerPositionPropertyInfo = IsDockRevealer
type AttrSetTypeConstraint DockRevealerPositionPropertyInfo = (~) Int32
type AttrTransferTypeConstraint DockRevealerPositionPropertyInfo = (~) Int32
type AttrTransferType DockRevealerPositionPropertyInfo = Int32
type AttrGetType DockRevealerPositionPropertyInfo = Int32
type AttrLabel DockRevealerPositionPropertyInfo = "position"
type AttrOrigin DockRevealerPositionPropertyInfo = DockRevealer
attrGet = getDockRevealerPosition
attrSet = setDockRevealerPosition
attrTransfer _ v = do
return v
attrConstruct = constructDockRevealerPosition
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockRevealer.position"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockRevealer.html#g:attr:position"
})
#endif
getDockRevealerPositionSet :: (MonadIO m, IsDockRevealer o) => o -> m Bool
getDockRevealerPositionSet :: forall (m :: * -> *) o.
(MonadIO m, IsDockRevealer o) =>
o -> m Bool
getDockRevealerPositionSet 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
"position-set"
setDockRevealerPositionSet :: (MonadIO m, IsDockRevealer o) => o -> Bool -> m ()
setDockRevealerPositionSet :: forall (m :: * -> *) o.
(MonadIO m, IsDockRevealer o) =>
o -> Bool -> m ()
setDockRevealerPositionSet 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
"position-set" Bool
val
constructDockRevealerPositionSet :: (IsDockRevealer o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructDockRevealerPositionSet :: forall o (m :: * -> *).
(IsDockRevealer o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructDockRevealerPositionSet 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
"position-set" Bool
val
#if defined(ENABLE_OVERLOADING)
data DockRevealerPositionSetPropertyInfo
instance AttrInfo DockRevealerPositionSetPropertyInfo where
type AttrAllowedOps DockRevealerPositionSetPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint DockRevealerPositionSetPropertyInfo = IsDockRevealer
type AttrSetTypeConstraint DockRevealerPositionSetPropertyInfo = (~) Bool
type AttrTransferTypeConstraint DockRevealerPositionSetPropertyInfo = (~) Bool
type AttrTransferType DockRevealerPositionSetPropertyInfo = Bool
type AttrGetType DockRevealerPositionSetPropertyInfo = Bool
type AttrLabel DockRevealerPositionSetPropertyInfo = "position-set"
type AttrOrigin DockRevealerPositionSetPropertyInfo = DockRevealer
attrGet = getDockRevealerPositionSet
attrSet = setDockRevealerPositionSet
attrTransfer _ v = do
return v
attrConstruct = constructDockRevealerPositionSet
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockRevealer.positionSet"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockRevealer.html#g:attr:positionSet"
})
#endif
getDockRevealerRevealChild :: (MonadIO m, IsDockRevealer o) => o -> m Bool
getDockRevealerRevealChild :: forall (m :: * -> *) o.
(MonadIO m, IsDockRevealer o) =>
o -> m Bool
getDockRevealerRevealChild 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
"reveal-child"
setDockRevealerRevealChild :: (MonadIO m, IsDockRevealer o) => o -> Bool -> m ()
setDockRevealerRevealChild :: forall (m :: * -> *) o.
(MonadIO m, IsDockRevealer o) =>
o -> Bool -> m ()
setDockRevealerRevealChild 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
"reveal-child" Bool
val
constructDockRevealerRevealChild :: (IsDockRevealer o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructDockRevealerRevealChild :: forall o (m :: * -> *).
(IsDockRevealer o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructDockRevealerRevealChild 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
"reveal-child" Bool
val
#if defined(ENABLE_OVERLOADING)
data DockRevealerRevealChildPropertyInfo
instance AttrInfo DockRevealerRevealChildPropertyInfo where
type AttrAllowedOps DockRevealerRevealChildPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint DockRevealerRevealChildPropertyInfo = IsDockRevealer
type AttrSetTypeConstraint DockRevealerRevealChildPropertyInfo = (~) Bool
type AttrTransferTypeConstraint DockRevealerRevealChildPropertyInfo = (~) Bool
type AttrTransferType DockRevealerRevealChildPropertyInfo = Bool
type AttrGetType DockRevealerRevealChildPropertyInfo = Bool
type AttrLabel DockRevealerRevealChildPropertyInfo = "reveal-child"
type AttrOrigin DockRevealerRevealChildPropertyInfo = DockRevealer
attrGet = getDockRevealerRevealChild
attrSet = setDockRevealerRevealChild
attrTransfer _ v = do
return v
attrConstruct = constructDockRevealerRevealChild
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockRevealer.revealChild"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockRevealer.html#g:attr:revealChild"
})
#endif
getDockRevealerTransitionDuration :: (MonadIO m, IsDockRevealer o) => o -> m Word32
getDockRevealerTransitionDuration :: forall (m :: * -> *) o.
(MonadIO m, IsDockRevealer o) =>
o -> m Word32
getDockRevealerTransitionDuration o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"transition-duration"
setDockRevealerTransitionDuration :: (MonadIO m, IsDockRevealer o) => o -> Word32 -> m ()
setDockRevealerTransitionDuration :: forall (m :: * -> *) o.
(MonadIO m, IsDockRevealer o) =>
o -> Word32 -> m ()
setDockRevealerTransitionDuration o
obj Word32
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 -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"transition-duration" Word32
val
constructDockRevealerTransitionDuration :: (IsDockRevealer o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructDockRevealerTransitionDuration :: forall o (m :: * -> *).
(IsDockRevealer o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructDockRevealerTransitionDuration Word32
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 -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"transition-duration" Word32
val
#if defined(ENABLE_OVERLOADING)
data DockRevealerTransitionDurationPropertyInfo
instance AttrInfo DockRevealerTransitionDurationPropertyInfo where
type AttrAllowedOps DockRevealerTransitionDurationPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint DockRevealerTransitionDurationPropertyInfo = IsDockRevealer
type AttrSetTypeConstraint DockRevealerTransitionDurationPropertyInfo = (~) Word32
type AttrTransferTypeConstraint DockRevealerTransitionDurationPropertyInfo = (~) Word32
type AttrTransferType DockRevealerTransitionDurationPropertyInfo = Word32
type AttrGetType DockRevealerTransitionDurationPropertyInfo = Word32
type AttrLabel DockRevealerTransitionDurationPropertyInfo = "transition-duration"
type AttrOrigin DockRevealerTransitionDurationPropertyInfo = DockRevealer
attrGet = getDockRevealerTransitionDuration
attrSet = setDockRevealerTransitionDuration
attrTransfer _ v = do
return v
attrConstruct = constructDockRevealerTransitionDuration
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockRevealer.transitionDuration"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockRevealer.html#g:attr:transitionDuration"
})
#endif
getDockRevealerTransitionType :: (MonadIO m, IsDockRevealer o) => o -> m Dazzle.Enums.DockRevealerTransitionType
getDockRevealerTransitionType :: forall (m :: * -> *) o.
(MonadIO m, IsDockRevealer o) =>
o -> m DockRevealerTransitionType
getDockRevealerTransitionType o
obj = IO DockRevealerTransitionType -> m DockRevealerTransitionType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO DockRevealerTransitionType -> m DockRevealerTransitionType)
-> IO DockRevealerTransitionType -> m DockRevealerTransitionType
forall a b. (a -> b) -> a -> b
$ o -> String -> IO DockRevealerTransitionType
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"transition-type"
setDockRevealerTransitionType :: (MonadIO m, IsDockRevealer o) => o -> Dazzle.Enums.DockRevealerTransitionType -> m ()
setDockRevealerTransitionType :: forall (m :: * -> *) o.
(MonadIO m, IsDockRevealer o) =>
o -> DockRevealerTransitionType -> m ()
setDockRevealerTransitionType o
obj DockRevealerTransitionType
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 -> DockRevealerTransitionType -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"transition-type" DockRevealerTransitionType
val
constructDockRevealerTransitionType :: (IsDockRevealer o, MIO.MonadIO m) => Dazzle.Enums.DockRevealerTransitionType -> m (GValueConstruct o)
constructDockRevealerTransitionType :: forall o (m :: * -> *).
(IsDockRevealer o, MonadIO m) =>
DockRevealerTransitionType -> m (GValueConstruct o)
constructDockRevealerTransitionType DockRevealerTransitionType
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 -> DockRevealerTransitionType -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"transition-type" DockRevealerTransitionType
val
#if defined(ENABLE_OVERLOADING)
data DockRevealerTransitionTypePropertyInfo
instance AttrInfo DockRevealerTransitionTypePropertyInfo where
type AttrAllowedOps DockRevealerTransitionTypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint DockRevealerTransitionTypePropertyInfo = IsDockRevealer
type AttrSetTypeConstraint DockRevealerTransitionTypePropertyInfo = (~) Dazzle.Enums.DockRevealerTransitionType
type AttrTransferTypeConstraint DockRevealerTransitionTypePropertyInfo = (~) Dazzle.Enums.DockRevealerTransitionType
type AttrTransferType DockRevealerTransitionTypePropertyInfo = Dazzle.Enums.DockRevealerTransitionType
type AttrGetType DockRevealerTransitionTypePropertyInfo = Dazzle.Enums.DockRevealerTransitionType
type AttrLabel DockRevealerTransitionTypePropertyInfo = "transition-type"
type AttrOrigin DockRevealerTransitionTypePropertyInfo = DockRevealer
attrGet = getDockRevealerTransitionType
attrSet = setDockRevealerTransitionType
attrTransfer _ v = do
return v
attrConstruct = constructDockRevealerTransitionType
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockRevealer.transitionType"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockRevealer.html#g:attr:transitionType"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DockRevealer
type instance O.AttributeList DockRevealer = DockRevealerAttributeList
type DockRevealerAttributeList = ('[ '("appPaintable", Gtk.Widget.WidgetAppPaintablePropertyInfo), '("borderWidth", Gtk.Container.ContainerBorderWidthPropertyInfo), '("canDefault", Gtk.Widget.WidgetCanDefaultPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("child", Gtk.Container.ContainerChildPropertyInfo), '("childRevealed", DockRevealerChildRevealedPropertyInfo), '("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), '("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), '("position", DockRevealerPositionPropertyInfo), '("positionSet", DockRevealerPositionSetPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("resizeMode", Gtk.Container.ContainerResizeModePropertyInfo), '("revealChild", DockRevealerRevealChildPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("style", Gtk.Widget.WidgetStylePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("transitionDuration", DockRevealerTransitionDurationPropertyInfo), '("transitionType", DockRevealerTransitionTypePropertyInfo), '("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)
dockRevealerChildRevealed :: AttrLabelProxy "childRevealed"
dockRevealerChildRevealed = AttrLabelProxy
dockRevealerPosition :: AttrLabelProxy "position"
dockRevealerPosition = AttrLabelProxy
dockRevealerPositionSet :: AttrLabelProxy "positionSet"
dockRevealerPositionSet = AttrLabelProxy
dockRevealerRevealChild :: AttrLabelProxy "revealChild"
dockRevealerRevealChild = AttrLabelProxy
dockRevealerTransitionDuration :: AttrLabelProxy "transitionDuration"
dockRevealerTransitionDuration = AttrLabelProxy
dockRevealerTransitionType :: AttrLabelProxy "transitionType"
dockRevealerTransitionType = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DockRevealer = DockRevealerSignalList
type DockRevealerSignalList = ('[ '("accelClosuresChanged", Gtk.Widget.WidgetAccelClosuresChangedSignalInfo), '("add", Gtk.Container.ContainerAddSignalInfo), '("buttonPressEvent", Gtk.Widget.WidgetButtonPressEventSignalInfo), '("buttonReleaseEvent", Gtk.Widget.WidgetButtonReleaseEventSignalInfo), '("canActivateAccel", Gtk.Widget.WidgetCanActivateAccelSignalInfo), '("checkResize", Gtk.Container.ContainerCheckResizeSignalInfo), '("childNotify", Gtk.Widget.WidgetChildNotifySignalInfo), '("compositedChanged", Gtk.Widget.WidgetCompositedChangedSignalInfo), '("configureEvent", Gtk.Widget.WidgetConfigureEventSignalInfo), '("damageEvent", Gtk.Widget.WidgetDamageEventSignalInfo), '("deleteEvent", Gtk.Widget.WidgetDeleteEventSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("destroyEvent", Gtk.Widget.WidgetDestroyEventSignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("dragBegin", Gtk.Widget.WidgetDragBeginSignalInfo), '("dragDataDelete", Gtk.Widget.WidgetDragDataDeleteSignalInfo), '("dragDataGet", Gtk.Widget.WidgetDragDataGetSignalInfo), '("dragDataReceived", Gtk.Widget.WidgetDragDataReceivedSignalInfo), '("dragDrop", Gtk.Widget.WidgetDragDropSignalInfo), '("dragEnd", Gtk.Widget.WidgetDragEndSignalInfo), '("dragFailed", Gtk.Widget.WidgetDragFailedSignalInfo), '("dragLeave", Gtk.Widget.WidgetDragLeaveSignalInfo), '("dragMotion", Gtk.Widget.WidgetDragMotionSignalInfo), '("draw", Gtk.Widget.WidgetDrawSignalInfo), '("enterNotifyEvent", Gtk.Widget.WidgetEnterNotifyEventSignalInfo), '("event", Gtk.Widget.WidgetEventSignalInfo), '("eventAfter", Gtk.Widget.WidgetEventAfterSignalInfo), '("focus", Gtk.Widget.WidgetFocusSignalInfo), '("focusInEvent", Gtk.Widget.WidgetFocusInEventSignalInfo), '("focusOutEvent", Gtk.Widget.WidgetFocusOutEventSignalInfo), '("grabBrokenEvent", Gtk.Widget.WidgetGrabBrokenEventSignalInfo), '("grabFocus", Gtk.Widget.WidgetGrabFocusSignalInfo), '("grabNotify", Gtk.Widget.WidgetGrabNotifySignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("hierarchyChanged", Gtk.Widget.WidgetHierarchyChangedSignalInfo), '("keyPressEvent", Gtk.Widget.WidgetKeyPressEventSignalInfo), '("keyReleaseEvent", Gtk.Widget.WidgetKeyReleaseEventSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("leaveNotifyEvent", Gtk.Widget.WidgetLeaveNotifyEventSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mapEvent", Gtk.Widget.WidgetMapEventSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("motionNotifyEvent", Gtk.Widget.WidgetMotionNotifyEventSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("parentSet", Gtk.Widget.WidgetParentSetSignalInfo), '("popupMenu", Gtk.Widget.WidgetPopupMenuSignalInfo), '("propertyNotifyEvent", Gtk.Widget.WidgetPropertyNotifyEventSignalInfo), '("proximityInEvent", Gtk.Widget.WidgetProximityInEventSignalInfo), '("proximityOutEvent", Gtk.Widget.WidgetProximityOutEventSignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("remove", Gtk.Container.ContainerRemoveSignalInfo), '("screenChanged", Gtk.Widget.WidgetScreenChangedSignalInfo), '("scrollEvent", Gtk.Widget.WidgetScrollEventSignalInfo), '("selectionClearEvent", Gtk.Widget.WidgetSelectionClearEventSignalInfo), '("selectionGet", Gtk.Widget.WidgetSelectionGetSignalInfo), '("selectionNotifyEvent", Gtk.Widget.WidgetSelectionNotifyEventSignalInfo), '("selectionReceived", Gtk.Widget.WidgetSelectionReceivedSignalInfo), '("selectionRequestEvent", Gtk.Widget.WidgetSelectionRequestEventSignalInfo), '("setFocusChild", Gtk.Container.ContainerSetFocusChildSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("showHelp", Gtk.Widget.WidgetShowHelpSignalInfo), '("sizeAllocate", Gtk.Widget.WidgetSizeAllocateSignalInfo), '("stateChanged", Gtk.Widget.WidgetStateChangedSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("styleSet", Gtk.Widget.WidgetStyleSetSignalInfo), '("styleUpdated", Gtk.Widget.WidgetStyleUpdatedSignalInfo), '("touchEvent", Gtk.Widget.WidgetTouchEventSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unmapEvent", Gtk.Widget.WidgetUnmapEventSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo), '("visibilityNotifyEvent", Gtk.Widget.WidgetVisibilityNotifyEventSignalInfo), '("windowStateEvent", Gtk.Widget.WidgetWindowStateEventSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "dzl_dock_revealer_new" dzl_dock_revealer_new ::
IO (Ptr DockRevealer)
dockRevealerNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m DockRevealer
dockRevealerNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m DockRevealer
dockRevealerNew = IO DockRevealer -> m DockRevealer
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DockRevealer -> m DockRevealer)
-> IO DockRevealer -> m DockRevealer
forall a b. (a -> b) -> a -> b
$ do
Ptr DockRevealer
result <- IO (Ptr DockRevealer)
dzl_dock_revealer_new
Text -> Ptr DockRevealer -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dockRevealerNew" Ptr DockRevealer
result
DockRevealer
result' <- ((ManagedPtr DockRevealer -> DockRevealer)
-> Ptr DockRevealer -> IO DockRevealer
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DockRevealer -> DockRevealer
DockRevealer) Ptr DockRevealer
result
DockRevealer -> IO DockRevealer
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return DockRevealer
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "dzl_dock_revealer_animate_to_position" dzl_dock_revealer_animate_to_position ::
Ptr DockRevealer ->
Int32 ->
Word32 ->
IO ()
dockRevealerAnimateToPosition ::
(B.CallStack.HasCallStack, MonadIO m, IsDockRevealer a) =>
a
-> Int32
-> Word32
-> m ()
dockRevealerAnimateToPosition :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDockRevealer a) =>
a -> Int32 -> Word32 -> m ()
dockRevealerAnimateToPosition a
self Int32
position Word32
transitionDuration = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr DockRevealer
self' <- a -> IO (Ptr DockRevealer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr DockRevealer -> Int32 -> Word32 -> IO ()
dzl_dock_revealer_animate_to_position Ptr DockRevealer
self' Int32
position Word32
transitionDuration
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DockRevealerAnimateToPositionMethodInfo
instance (signature ~ (Int32 -> Word32 -> m ()), MonadIO m, IsDockRevealer a) => O.OverloadedMethod DockRevealerAnimateToPositionMethodInfo a signature where
overloadedMethod = dockRevealerAnimateToPosition
instance O.OverloadedMethodInfo DockRevealerAnimateToPositionMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockRevealer.dockRevealerAnimateToPosition",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockRevealer.html#v:dockRevealerAnimateToPosition"
})
#endif
foreign import ccall "dzl_dock_revealer_get_child_revealed" dzl_dock_revealer_get_child_revealed ::
Ptr DockRevealer ->
IO CInt
dockRevealerGetChildRevealed ::
(B.CallStack.HasCallStack, MonadIO m, IsDockRevealer a) =>
a
-> m Bool
dockRevealerGetChildRevealed :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDockRevealer a) =>
a -> m Bool
dockRevealerGetChildRevealed a
self = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr DockRevealer
self' <- a -> IO (Ptr DockRevealer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CInt
result <- Ptr DockRevealer -> IO CInt
dzl_dock_revealer_get_child_revealed Ptr DockRevealer
self'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DockRevealerGetChildRevealedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDockRevealer a) => O.OverloadedMethod DockRevealerGetChildRevealedMethodInfo a signature where
overloadedMethod = dockRevealerGetChildRevealed
instance O.OverloadedMethodInfo DockRevealerGetChildRevealedMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockRevealer.dockRevealerGetChildRevealed",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockRevealer.html#v:dockRevealerGetChildRevealed"
})
#endif
foreign import ccall "dzl_dock_revealer_get_position" dzl_dock_revealer_get_position ::
Ptr DockRevealer ->
IO Int32
dockRevealerGetPosition ::
(B.CallStack.HasCallStack, MonadIO m, IsDockRevealer a) =>
a
-> m Int32
dockRevealerGetPosition :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDockRevealer a) =>
a -> m Int32
dockRevealerGetPosition a
self = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
Ptr DockRevealer
self' <- a -> IO (Ptr DockRevealer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Int32
result <- Ptr DockRevealer -> IO Int32
dzl_dock_revealer_get_position Ptr DockRevealer
self'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data DockRevealerGetPositionMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsDockRevealer a) => O.OverloadedMethod DockRevealerGetPositionMethodInfo a signature where
overloadedMethod = dockRevealerGetPosition
instance O.OverloadedMethodInfo DockRevealerGetPositionMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockRevealer.dockRevealerGetPosition",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockRevealer.html#v:dockRevealerGetPosition"
})
#endif
foreign import ccall "dzl_dock_revealer_get_position_set" dzl_dock_revealer_get_position_set ::
Ptr DockRevealer ->
IO CInt
dockRevealerGetPositionSet ::
(B.CallStack.HasCallStack, MonadIO m, IsDockRevealer a) =>
a
-> m Bool
dockRevealerGetPositionSet :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDockRevealer a) =>
a -> m Bool
dockRevealerGetPositionSet a
self = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr DockRevealer
self' <- a -> IO (Ptr DockRevealer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CInt
result <- Ptr DockRevealer -> IO CInt
dzl_dock_revealer_get_position_set Ptr DockRevealer
self'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DockRevealerGetPositionSetMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDockRevealer a) => O.OverloadedMethod DockRevealerGetPositionSetMethodInfo a signature where
overloadedMethod = dockRevealerGetPositionSet
instance O.OverloadedMethodInfo DockRevealerGetPositionSetMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockRevealer.dockRevealerGetPositionSet",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockRevealer.html#v:dockRevealerGetPositionSet"
})
#endif
foreign import ccall "dzl_dock_revealer_get_reveal_child" dzl_dock_revealer_get_reveal_child ::
Ptr DockRevealer ->
IO CInt
dockRevealerGetRevealChild ::
(B.CallStack.HasCallStack, MonadIO m, IsDockRevealer a) =>
a
-> m Bool
dockRevealerGetRevealChild :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDockRevealer a) =>
a -> m Bool
dockRevealerGetRevealChild a
self = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr DockRevealer
self' <- a -> IO (Ptr DockRevealer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CInt
result <- Ptr DockRevealer -> IO CInt
dzl_dock_revealer_get_reveal_child Ptr DockRevealer
self'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DockRevealerGetRevealChildMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDockRevealer a) => O.OverloadedMethod DockRevealerGetRevealChildMethodInfo a signature where
overloadedMethod = dockRevealerGetRevealChild
instance O.OverloadedMethodInfo DockRevealerGetRevealChildMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockRevealer.dockRevealerGetRevealChild",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockRevealer.html#v:dockRevealerGetRevealChild"
})
#endif
foreign import ccall "dzl_dock_revealer_get_transition_duration" dzl_dock_revealer_get_transition_duration ::
Ptr DockRevealer ->
IO Word32
dockRevealerGetTransitionDuration ::
(B.CallStack.HasCallStack, MonadIO m, IsDockRevealer a) =>
a
-> m Word32
dockRevealerGetTransitionDuration :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDockRevealer a) =>
a -> m Word32
dockRevealerGetTransitionDuration a
self = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
Ptr DockRevealer
self' <- a -> IO (Ptr DockRevealer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Word32
result <- Ptr DockRevealer -> IO Word32
dzl_dock_revealer_get_transition_duration Ptr DockRevealer
self'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data DockRevealerGetTransitionDurationMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsDockRevealer a) => O.OverloadedMethod DockRevealerGetTransitionDurationMethodInfo a signature where
overloadedMethod = dockRevealerGetTransitionDuration
instance O.OverloadedMethodInfo DockRevealerGetTransitionDurationMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockRevealer.dockRevealerGetTransitionDuration",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockRevealer.html#v:dockRevealerGetTransitionDuration"
})
#endif
foreign import ccall "dzl_dock_revealer_get_transition_type" dzl_dock_revealer_get_transition_type ::
Ptr DockRevealer ->
IO CUInt
dockRevealerGetTransitionType ::
(B.CallStack.HasCallStack, MonadIO m, IsDockRevealer a) =>
a
-> m Dazzle.Enums.DockRevealerTransitionType
dockRevealerGetTransitionType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDockRevealer a) =>
a -> m DockRevealerTransitionType
dockRevealerGetTransitionType a
self = IO DockRevealerTransitionType -> m DockRevealerTransitionType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DockRevealerTransitionType -> m DockRevealerTransitionType)
-> IO DockRevealerTransitionType -> m DockRevealerTransitionType
forall a b. (a -> b) -> a -> b
$ do
Ptr DockRevealer
self' <- a -> IO (Ptr DockRevealer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CUInt
result <- Ptr DockRevealer -> IO CUInt
dzl_dock_revealer_get_transition_type Ptr DockRevealer
self'
let result' :: DockRevealerTransitionType
result' = (Int -> DockRevealerTransitionType
forall a. Enum a => Int -> a
toEnum (Int -> DockRevealerTransitionType)
-> (CUInt -> Int) -> CUInt -> DockRevealerTransitionType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
DockRevealerTransitionType -> IO DockRevealerTransitionType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return DockRevealerTransitionType
result'
#if defined(ENABLE_OVERLOADING)
data DockRevealerGetTransitionTypeMethodInfo
instance (signature ~ (m Dazzle.Enums.DockRevealerTransitionType), MonadIO m, IsDockRevealer a) => O.OverloadedMethod DockRevealerGetTransitionTypeMethodInfo a signature where
overloadedMethod = dockRevealerGetTransitionType
instance O.OverloadedMethodInfo DockRevealerGetTransitionTypeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockRevealer.dockRevealerGetTransitionType",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockRevealer.html#v:dockRevealerGetTransitionType"
})
#endif
foreign import ccall "dzl_dock_revealer_is_animating" dzl_dock_revealer_is_animating ::
Ptr DockRevealer ->
IO CInt
dockRevealerIsAnimating ::
(B.CallStack.HasCallStack, MonadIO m, IsDockRevealer a) =>
a
-> m Bool
dockRevealerIsAnimating :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDockRevealer a) =>
a -> m Bool
dockRevealerIsAnimating a
self = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr DockRevealer
self' <- a -> IO (Ptr DockRevealer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CInt
result <- Ptr DockRevealer -> IO CInt
dzl_dock_revealer_is_animating Ptr DockRevealer
self'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DockRevealerIsAnimatingMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDockRevealer a) => O.OverloadedMethod DockRevealerIsAnimatingMethodInfo a signature where
overloadedMethod = dockRevealerIsAnimating
instance O.OverloadedMethodInfo DockRevealerIsAnimatingMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockRevealer.dockRevealerIsAnimating",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockRevealer.html#v:dockRevealerIsAnimating"
})
#endif
foreign import ccall "dzl_dock_revealer_set_position" dzl_dock_revealer_set_position ::
Ptr DockRevealer ->
Int32 ->
IO ()
dockRevealerSetPosition ::
(B.CallStack.HasCallStack, MonadIO m, IsDockRevealer a) =>
a
-> Int32
-> m ()
dockRevealerSetPosition :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDockRevealer a) =>
a -> Int32 -> m ()
dockRevealerSetPosition a
self Int32
position = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr DockRevealer
self' <- a -> IO (Ptr DockRevealer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr DockRevealer -> Int32 -> IO ()
dzl_dock_revealer_set_position Ptr DockRevealer
self' Int32
position
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DockRevealerSetPositionMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsDockRevealer a) => O.OverloadedMethod DockRevealerSetPositionMethodInfo a signature where
overloadedMethod = dockRevealerSetPosition
instance O.OverloadedMethodInfo DockRevealerSetPositionMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockRevealer.dockRevealerSetPosition",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockRevealer.html#v:dockRevealerSetPosition"
})
#endif
foreign import ccall "dzl_dock_revealer_set_position_set" dzl_dock_revealer_set_position_set ::
Ptr DockRevealer ->
CInt ->
IO ()
dockRevealerSetPositionSet ::
(B.CallStack.HasCallStack, MonadIO m, IsDockRevealer a) =>
a
-> Bool
-> m ()
dockRevealerSetPositionSet :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDockRevealer a) =>
a -> Bool -> m ()
dockRevealerSetPositionSet a
self Bool
positionSet = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr DockRevealer
self' <- a -> IO (Ptr DockRevealer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
let positionSet' :: CInt
positionSet' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
positionSet
Ptr DockRevealer -> CInt -> IO ()
dzl_dock_revealer_set_position_set Ptr DockRevealer
self' CInt
positionSet'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DockRevealerSetPositionSetMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsDockRevealer a) => O.OverloadedMethod DockRevealerSetPositionSetMethodInfo a signature where
overloadedMethod = dockRevealerSetPositionSet
instance O.OverloadedMethodInfo DockRevealerSetPositionSetMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockRevealer.dockRevealerSetPositionSet",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockRevealer.html#v:dockRevealerSetPositionSet"
})
#endif
foreign import ccall "dzl_dock_revealer_set_reveal_child" dzl_dock_revealer_set_reveal_child ::
Ptr DockRevealer ->
CInt ->
IO ()
dockRevealerSetRevealChild ::
(B.CallStack.HasCallStack, MonadIO m, IsDockRevealer a) =>
a
-> Bool
-> m ()
dockRevealerSetRevealChild :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDockRevealer a) =>
a -> Bool -> m ()
dockRevealerSetRevealChild a
self Bool
revealChild = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr DockRevealer
self' <- a -> IO (Ptr DockRevealer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
let revealChild' :: CInt
revealChild' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
revealChild
Ptr DockRevealer -> CInt -> IO ()
dzl_dock_revealer_set_reveal_child Ptr DockRevealer
self' CInt
revealChild'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DockRevealerSetRevealChildMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsDockRevealer a) => O.OverloadedMethod DockRevealerSetRevealChildMethodInfo a signature where
overloadedMethod = dockRevealerSetRevealChild
instance O.OverloadedMethodInfo DockRevealerSetRevealChildMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockRevealer.dockRevealerSetRevealChild",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockRevealer.html#v:dockRevealerSetRevealChild"
})
#endif
foreign import ccall "dzl_dock_revealer_set_transition_duration" dzl_dock_revealer_set_transition_duration ::
Ptr DockRevealer ->
Word32 ->
IO ()
dockRevealerSetTransitionDuration ::
(B.CallStack.HasCallStack, MonadIO m, IsDockRevealer a) =>
a
-> Word32
-> m ()
dockRevealerSetTransitionDuration :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDockRevealer a) =>
a -> Word32 -> m ()
dockRevealerSetTransitionDuration a
self Word32
transitionDuration = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr DockRevealer
self' <- a -> IO (Ptr DockRevealer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr DockRevealer -> Word32 -> IO ()
dzl_dock_revealer_set_transition_duration Ptr DockRevealer
self' Word32
transitionDuration
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DockRevealerSetTransitionDurationMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDockRevealer a) => O.OverloadedMethod DockRevealerSetTransitionDurationMethodInfo a signature where
overloadedMethod = dockRevealerSetTransitionDuration
instance O.OverloadedMethodInfo DockRevealerSetTransitionDurationMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockRevealer.dockRevealerSetTransitionDuration",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockRevealer.html#v:dockRevealerSetTransitionDuration"
})
#endif
foreign import ccall "dzl_dock_revealer_set_transition_type" dzl_dock_revealer_set_transition_type ::
Ptr DockRevealer ->
CUInt ->
IO ()
dockRevealerSetTransitionType ::
(B.CallStack.HasCallStack, MonadIO m, IsDockRevealer a) =>
a
-> Dazzle.Enums.DockRevealerTransitionType
-> m ()
dockRevealerSetTransitionType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDockRevealer a) =>
a -> DockRevealerTransitionType -> m ()
dockRevealerSetTransitionType a
self DockRevealerTransitionType
transitionType = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr DockRevealer
self' <- a -> IO (Ptr DockRevealer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
let transitionType' :: CUInt
transitionType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (DockRevealerTransitionType -> Int)
-> DockRevealerTransitionType
-> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DockRevealerTransitionType -> Int
forall a. Enum a => a -> Int
fromEnum) DockRevealerTransitionType
transitionType
Ptr DockRevealer -> CUInt -> IO ()
dzl_dock_revealer_set_transition_type Ptr DockRevealer
self' CUInt
transitionType'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DockRevealerSetTransitionTypeMethodInfo
instance (signature ~ (Dazzle.Enums.DockRevealerTransitionType -> m ()), MonadIO m, IsDockRevealer a) => O.OverloadedMethod DockRevealerSetTransitionTypeMethodInfo a signature where
overloadedMethod = dockRevealerSetTransitionType
instance O.OverloadedMethodInfo DockRevealerSetTransitionTypeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.DockRevealer.dockRevealerSetTransitionType",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockRevealer.html#v:dockRevealerSetTransitionType"
})
#endif