{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Together with t'GI.Gtk.Objects.Socket.Socket', t'GI.Gtk.Objects.Plug.Plug' provides the ability to embed
-- widgets from one process into another process in a fashion that is
-- transparent to the user. One process creates a t'GI.Gtk.Objects.Socket.Socket' widget
-- and passes the ID of that widget’s window to the other process,
-- which then creates a t'GI.Gtk.Objects.Plug.Plug' with that window ID. Any widgets
-- contained in the t'GI.Gtk.Objects.Plug.Plug' then will appear inside the first
-- application’s window.
-- 
-- The communication between a t'GI.Gtk.Objects.Socket.Socket' and a t'GI.Gtk.Objects.Plug.Plug' follows the
-- <http://www.freedesktop.org/Standards/xembed-spec XEmbed Protocol>.
-- This protocol has also been implemented in other toolkits, e.g. Qt,
-- allowing the same level of integration when embedding a Qt widget
-- in GTK+ or vice versa.
-- 
-- The t'GI.Gtk.Objects.Plug.Plug' and t'GI.Gtk.Objects.Socket.Socket' widgets are only available when GTK+
-- is compiled for the X11 platform and @/GDK_WINDOWING_X11/@ is defined.
-- They can only be used on a @/GdkX11Display/@. To use t'GI.Gtk.Objects.Plug.Plug' and
-- t'GI.Gtk.Objects.Socket.Socket', you need to include the @gtk\/gtkx.h@ header.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Gtk.Objects.Plug
    ( 

-- * Exported types
    Plug(..)                                ,
    IsPlug                                  ,
    toPlug                                  ,
    noPlug                                  ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolvePlugMethod                       ,
#endif


-- ** construct #method:construct#

#if defined(ENABLE_OVERLOADING)
    PlugConstructMethodInfo                 ,
#endif
    plugConstruct                           ,


-- ** constructForDisplay #method:constructForDisplay#

#if defined(ENABLE_OVERLOADING)
    PlugConstructForDisplayMethodInfo       ,
#endif
    plugConstructForDisplay                 ,


-- ** getEmbedded #method:getEmbedded#

#if defined(ENABLE_OVERLOADING)
    PlugGetEmbeddedMethodInfo               ,
#endif
    plugGetEmbedded                         ,


-- ** getId #method:getId#

#if defined(ENABLE_OVERLOADING)
    PlugGetIdMethodInfo                     ,
#endif
    plugGetId                               ,


-- ** getSocketWindow #method:getSocketWindow#

#if defined(ENABLE_OVERLOADING)
    PlugGetSocketWindowMethodInfo           ,
#endif
    plugGetSocketWindow                     ,


-- ** new #method:new#

    plugNew                                 ,


-- ** newForDisplay #method:newForDisplay#

    plugNewForDisplay                       ,




 -- * Properties
-- ** embedded #attr:embedded#
-- | 'P.True' if the plug is embedded in a socket.
-- 
-- /Since: 2.12/

#if defined(ENABLE_OVERLOADING)
    PlugEmbeddedPropertyInfo                ,
#endif
    getPlugEmbedded                         ,
#if defined(ENABLE_OVERLOADING)
    plugEmbedded                            ,
#endif


-- ** socketWindow #attr:socketWindow#
-- | The window of the socket the plug is embedded in.
-- 
-- /Since: 2.14/

#if defined(ENABLE_OVERLOADING)
    PlugSocketWindowPropertyInfo            ,
#endif
    getPlugSocketWindow                     ,
#if defined(ENABLE_OVERLOADING)
    plugSocketWindow                        ,
#endif




 -- * Signals
-- ** embedded #signal:embedded#

    C_PlugEmbeddedCallback                  ,
    PlugEmbeddedCallback                    ,
#if defined(ENABLE_OVERLOADING)
    PlugEmbeddedSignalInfo                  ,
#endif
    afterPlugEmbedded                       ,
    genClosure_PlugEmbedded                 ,
    mk_PlugEmbeddedCallback                 ,
    noPlugEmbeddedCallback                  ,
    onPlugEmbedded                          ,
    wrap_PlugEmbeddedCallback               ,




    ) 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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
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 Data.Text as T
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 GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Objects.Display as Gdk.Display
import qualified GI.Gdk.Objects.Window as Gdk.Window
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Objects.Bin as Gtk.Bin
import {-# SOURCE #-} qualified GI.Gtk.Objects.Container as Gtk.Container
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
import {-# SOURCE #-} qualified GI.Gtk.Objects.Window as Gtk.Window

-- | Memory-managed wrapper type.
newtype Plug = Plug (ManagedPtr Plug)
    deriving (Plug -> Plug -> Bool
(Plug -> Plug -> Bool) -> (Plug -> Plug -> Bool) -> Eq Plug
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Plug -> Plug -> Bool
$c/= :: Plug -> Plug -> Bool
== :: Plug -> Plug -> Bool
$c== :: Plug -> Plug -> Bool
Eq)
foreign import ccall "gtk_plug_get_type"
    c_gtk_plug_get_type :: IO GType

instance GObject Plug where
    gobjectType :: IO GType
gobjectType = IO GType
c_gtk_plug_get_type
    

-- | Convert 'Plug' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue Plug where
    toGValue :: Plug -> IO GValue
toGValue o :: Plug
o = do
        GType
gtype <- IO GType
c_gtk_plug_get_type
        Plug -> (Ptr Plug -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Plug
o (GType -> (GValue -> Ptr Plug -> IO ()) -> Ptr Plug -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Plug -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO Plug
fromGValue gv :: GValue
gv = do
        Ptr Plug
ptr <- GValue -> IO (Ptr Plug)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Plug)
        (ManagedPtr Plug -> Plug) -> Ptr Plug -> IO Plug
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Plug -> Plug
Plug Ptr Plug
ptr
        
    

-- | Type class for types which can be safely cast to `Plug`, for instance with `toPlug`.
class (GObject o, O.IsDescendantOf Plug o) => IsPlug o
instance (GObject o, O.IsDescendantOf Plug o) => IsPlug o

instance O.HasParentTypes Plug
type instance O.ParentTypes Plug = '[Gtk.Window.Window, Gtk.Bin.Bin, Gtk.Container.Container, Gtk.Widget.Widget, GObject.Object.Object, Atk.ImplementorIface.ImplementorIface, Gtk.Buildable.Buildable]

-- | Cast to `Plug`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toPlug :: (MonadIO m, IsPlug o) => o -> m Plug
toPlug :: o -> m Plug
toPlug = IO Plug -> m Plug
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Plug -> m Plug) -> (o -> IO Plug) -> o -> m Plug
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Plug -> Plug) -> o -> IO Plug
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Plug -> Plug
Plug

-- | A convenience alias for `Nothing` :: `Maybe` `Plug`.
noPlug :: Maybe Plug
noPlug :: Maybe Plug
noPlug = Maybe Plug
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolvePlugMethod (t :: Symbol) (o :: *) :: * where
    ResolvePlugMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolvePlugMethod "activateDefault" o = Gtk.Window.WindowActivateDefaultMethodInfo
    ResolvePlugMethod "activateFocus" o = Gtk.Window.WindowActivateFocusMethodInfo
    ResolvePlugMethod "activateKey" o = Gtk.Window.WindowActivateKeyMethodInfo
    ResolvePlugMethod "add" o = Gtk.Container.ContainerAddMethodInfo
    ResolvePlugMethod "addAccelGroup" o = Gtk.Window.WindowAddAccelGroupMethodInfo
    ResolvePlugMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
    ResolvePlugMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
    ResolvePlugMethod "addDeviceEvents" o = Gtk.Widget.WidgetAddDeviceEventsMethodInfo
    ResolvePlugMethod "addEvents" o = Gtk.Widget.WidgetAddEventsMethodInfo
    ResolvePlugMethod "addMnemonic" o = Gtk.Window.WindowAddMnemonicMethodInfo
    ResolvePlugMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolvePlugMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolvePlugMethod "beginMoveDrag" o = Gtk.Window.WindowBeginMoveDragMethodInfo
    ResolvePlugMethod "beginResizeDrag" o = Gtk.Window.WindowBeginResizeDragMethodInfo
    ResolvePlugMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolvePlugMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolvePlugMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
    ResolvePlugMethod "checkResize" o = Gtk.Container.ContainerCheckResizeMethodInfo
    ResolvePlugMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolvePlugMethod "childGetProperty" o = Gtk.Container.ContainerChildGetPropertyMethodInfo
    ResolvePlugMethod "childNotify" o = Gtk.Container.ContainerChildNotifyMethodInfo
    ResolvePlugMethod "childNotifyByPspec" o = Gtk.Container.ContainerChildNotifyByPspecMethodInfo
    ResolvePlugMethod "childSetProperty" o = Gtk.Container.ContainerChildSetPropertyMethodInfo
    ResolvePlugMethod "childType" o = Gtk.Container.ContainerChildTypeMethodInfo
    ResolvePlugMethod "classPath" o = Gtk.Widget.WidgetClassPathMethodInfo
    ResolvePlugMethod "close" o = Gtk.Window.WindowCloseMethodInfo
    ResolvePlugMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolvePlugMethod "construct" o = PlugConstructMethodInfo
    ResolvePlugMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
    ResolvePlugMethod "constructForDisplay" o = PlugConstructForDisplayMethodInfo
    ResolvePlugMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolvePlugMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolvePlugMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
    ResolvePlugMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
    ResolvePlugMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
    ResolvePlugMethod "deiconify" o = Gtk.Window.WindowDeiconifyMethodInfo
    ResolvePlugMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
    ResolvePlugMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
    ResolvePlugMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
    ResolvePlugMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
    ResolvePlugMethod "dragBeginWithCoordinates" o = Gtk.Widget.WidgetDragBeginWithCoordinatesMethodInfo
    ResolvePlugMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolvePlugMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
    ResolvePlugMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
    ResolvePlugMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
    ResolvePlugMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
    ResolvePlugMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
    ResolvePlugMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
    ResolvePlugMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
    ResolvePlugMethod "dragDestSetProxy" o = Gtk.Widget.WidgetDragDestSetProxyMethodInfo
    ResolvePlugMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
    ResolvePlugMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
    ResolvePlugMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
    ResolvePlugMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
    ResolvePlugMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
    ResolvePlugMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
    ResolvePlugMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
    ResolvePlugMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
    ResolvePlugMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
    ResolvePlugMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
    ResolvePlugMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
    ResolvePlugMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
    ResolvePlugMethod "dragSourceSetIconPixbuf" o = Gtk.Widget.WidgetDragSourceSetIconPixbufMethodInfo
    ResolvePlugMethod "dragSourceSetIconStock" o = Gtk.Widget.WidgetDragSourceSetIconStockMethodInfo
    ResolvePlugMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
    ResolvePlugMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
    ResolvePlugMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
    ResolvePlugMethod "draw" o = Gtk.Widget.WidgetDrawMethodInfo
    ResolvePlugMethod "ensureStyle" o = Gtk.Widget.WidgetEnsureStyleMethodInfo
    ResolvePlugMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolvePlugMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
    ResolvePlugMethod "forall" o = Gtk.Container.ContainerForallMethodInfo
    ResolvePlugMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolvePlugMethod "foreach" o = Gtk.Container.ContainerForeachMethodInfo
    ResolvePlugMethod "freezeChildNotify" o = Gtk.Widget.WidgetFreezeChildNotifyMethodInfo
    ResolvePlugMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolvePlugMethod "fullscreen" o = Gtk.Window.WindowFullscreenMethodInfo
    ResolvePlugMethod "fullscreenOnMonitor" o = Gtk.Window.WindowFullscreenOnMonitorMethodInfo
    ResolvePlugMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolvePlugMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
    ResolvePlugMethod "grabDefault" o = Gtk.Widget.WidgetGrabDefaultMethodInfo
    ResolvePlugMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolvePlugMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
    ResolvePlugMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolvePlugMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolvePlugMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
    ResolvePlugMethod "hasGroup" o = Gtk.Window.WindowHasGroupMethodInfo
    ResolvePlugMethod "hasRcStyle" o = Gtk.Widget.WidgetHasRcStyleMethodInfo
    ResolvePlugMethod "hasScreen" o = Gtk.Widget.WidgetHasScreenMethodInfo
    ResolvePlugMethod "hasToplevelFocus" o = Gtk.Window.WindowHasToplevelFocusMethodInfo
    ResolvePlugMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolvePlugMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolvePlugMethod "hideOnDelete" o = Gtk.Widget.WidgetHideOnDeleteMethodInfo
    ResolvePlugMethod "iconify" o = Gtk.Window.WindowIconifyMethodInfo
    ResolvePlugMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolvePlugMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolvePlugMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
    ResolvePlugMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolvePlugMethod "intersect" o = Gtk.Widget.WidgetIntersectMethodInfo
    ResolvePlugMethod "isActive" o = Gtk.Window.WindowIsActiveMethodInfo
    ResolvePlugMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolvePlugMethod "isComposited" o = Gtk.Widget.WidgetIsCompositedMethodInfo
    ResolvePlugMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolvePlugMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolvePlugMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolvePlugMethod "isMaximized" o = Gtk.Window.WindowIsMaximizedMethodInfo
    ResolvePlugMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolvePlugMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
    ResolvePlugMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolvePlugMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolvePlugMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
    ResolvePlugMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
    ResolvePlugMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolvePlugMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolvePlugMethod "maximize" o = Gtk.Window.WindowMaximizeMethodInfo
    ResolvePlugMethod "mnemonicActivate" o = Gtk.Window.WindowMnemonicActivateMethodInfo
    ResolvePlugMethod "modifyBase" o = Gtk.Widget.WidgetModifyBaseMethodInfo
    ResolvePlugMethod "modifyBg" o = Gtk.Widget.WidgetModifyBgMethodInfo
    ResolvePlugMethod "modifyCursor" o = Gtk.Widget.WidgetModifyCursorMethodInfo
    ResolvePlugMethod "modifyFg" o = Gtk.Widget.WidgetModifyFgMethodInfo
    ResolvePlugMethod "modifyFont" o = Gtk.Widget.WidgetModifyFontMethodInfo
    ResolvePlugMethod "modifyStyle" o = Gtk.Widget.WidgetModifyStyleMethodInfo
    ResolvePlugMethod "modifyText" o = Gtk.Widget.WidgetModifyTextMethodInfo
    ResolvePlugMethod "move" o = Gtk.Window.WindowMoveMethodInfo
    ResolvePlugMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolvePlugMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolvePlugMethod "overrideBackgroundColor" o = Gtk.Widget.WidgetOverrideBackgroundColorMethodInfo
    ResolvePlugMethod "overrideColor" o = Gtk.Widget.WidgetOverrideColorMethodInfo
    ResolvePlugMethod "overrideCursor" o = Gtk.Widget.WidgetOverrideCursorMethodInfo
    ResolvePlugMethod "overrideFont" o = Gtk.Widget.WidgetOverrideFontMethodInfo
    ResolvePlugMethod "overrideSymbolicColor" o = Gtk.Widget.WidgetOverrideSymbolicColorMethodInfo
    ResolvePlugMethod "parseGeometry" o = Gtk.Window.WindowParseGeometryMethodInfo
    ResolvePlugMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
    ResolvePlugMethod "path" o = Gtk.Widget.WidgetPathMethodInfo
    ResolvePlugMethod "present" o = Gtk.Window.WindowPresentMethodInfo
    ResolvePlugMethod "presentWithTime" o = Gtk.Window.WindowPresentWithTimeMethodInfo
    ResolvePlugMethod "propagateDraw" o = Gtk.Container.ContainerPropagateDrawMethodInfo
    ResolvePlugMethod "propagateKeyEvent" o = Gtk.Window.WindowPropagateKeyEventMethodInfo
    ResolvePlugMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolvePlugMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
    ResolvePlugMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolvePlugMethod "queueDrawArea" o = Gtk.Widget.WidgetQueueDrawAreaMethodInfo
    ResolvePlugMethod "queueDrawRegion" o = Gtk.Widget.WidgetQueueDrawRegionMethodInfo
    ResolvePlugMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolvePlugMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
    ResolvePlugMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolvePlugMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolvePlugMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolvePlugMethod "regionIntersect" o = Gtk.Widget.WidgetRegionIntersectMethodInfo
    ResolvePlugMethod "registerWindow" o = Gtk.Widget.WidgetRegisterWindowMethodInfo
    ResolvePlugMethod "remove" o = Gtk.Container.ContainerRemoveMethodInfo
    ResolvePlugMethod "removeAccelGroup" o = Gtk.Window.WindowRemoveAccelGroupMethodInfo
    ResolvePlugMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
    ResolvePlugMethod "removeMnemonic" o = Gtk.Window.WindowRemoveMnemonicMethodInfo
    ResolvePlugMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolvePlugMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolvePlugMethod "renderIcon" o = Gtk.Widget.WidgetRenderIconMethodInfo
    ResolvePlugMethod "renderIconPixbuf" o = Gtk.Widget.WidgetRenderIconPixbufMethodInfo
    ResolvePlugMethod "reparent" o = Gtk.Widget.WidgetReparentMethodInfo
    ResolvePlugMethod "resetRcStyles" o = Gtk.Widget.WidgetResetRcStylesMethodInfo
    ResolvePlugMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
    ResolvePlugMethod "reshowWithInitialSize" o = Gtk.Window.WindowReshowWithInitialSizeMethodInfo
    ResolvePlugMethod "resize" o = Gtk.Window.WindowResizeMethodInfo
    ResolvePlugMethod "resizeChildren" o = Gtk.Container.ContainerResizeChildrenMethodInfo
    ResolvePlugMethod "resizeGripIsVisible" o = Gtk.Window.WindowResizeGripIsVisibleMethodInfo
    ResolvePlugMethod "resizeToGeometry" o = Gtk.Window.WindowResizeToGeometryMethodInfo
    ResolvePlugMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolvePlugMethod "sendExpose" o = Gtk.Widget.WidgetSendExposeMethodInfo
    ResolvePlugMethod "sendFocusChange" o = Gtk.Widget.WidgetSendFocusChangeMethodInfo
    ResolvePlugMethod "shapeCombineRegion" o = Gtk.Widget.WidgetShapeCombineRegionMethodInfo
    ResolvePlugMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolvePlugMethod "showAll" o = Gtk.Widget.WidgetShowAllMethodInfo
    ResolvePlugMethod "showNow" o = Gtk.Widget.WidgetShowNowMethodInfo
    ResolvePlugMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolvePlugMethod "sizeAllocateWithBaseline" o = Gtk.Widget.WidgetSizeAllocateWithBaselineMethodInfo
    ResolvePlugMethod "sizeRequest" o = Gtk.Widget.WidgetSizeRequestMethodInfo
    ResolvePlugMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolvePlugMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolvePlugMethod "stick" o = Gtk.Window.WindowStickMethodInfo
    ResolvePlugMethod "styleAttach" o = Gtk.Widget.WidgetStyleAttachMethodInfo
    ResolvePlugMethod "styleGetProperty" o = Gtk.Widget.WidgetStyleGetPropertyMethodInfo
    ResolvePlugMethod "thawChildNotify" o = Gtk.Widget.WidgetThawChildNotifyMethodInfo
    ResolvePlugMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolvePlugMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolvePlugMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolvePlugMethod "unfullscreen" o = Gtk.Window.WindowUnfullscreenMethodInfo
    ResolvePlugMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolvePlugMethod "unmaximize" o = Gtk.Window.WindowUnmaximizeMethodInfo
    ResolvePlugMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolvePlugMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolvePlugMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolvePlugMethod "unregisterWindow" o = Gtk.Widget.WidgetUnregisterWindowMethodInfo
    ResolvePlugMethod "unsetFocusChain" o = Gtk.Container.ContainerUnsetFocusChainMethodInfo
    ResolvePlugMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolvePlugMethod "unstick" o = Gtk.Window.WindowUnstickMethodInfo
    ResolvePlugMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolvePlugMethod "getAcceptFocus" o = Gtk.Window.WindowGetAcceptFocusMethodInfo
    ResolvePlugMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
    ResolvePlugMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
    ResolvePlugMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolvePlugMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolvePlugMethod "getAllocatedSize" o = Gtk.Widget.WidgetGetAllocatedSizeMethodInfo
    ResolvePlugMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolvePlugMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolvePlugMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolvePlugMethod "getAppPaintable" o = Gtk.Widget.WidgetGetAppPaintableMethodInfo
    ResolvePlugMethod "getApplication" o = Gtk.Window.WindowGetApplicationMethodInfo
    ResolvePlugMethod "getAttachedTo" o = Gtk.Window.WindowGetAttachedToMethodInfo
    ResolvePlugMethod "getBorderWidth" o = Gtk.Container.ContainerGetBorderWidthMethodInfo
    ResolvePlugMethod "getCanDefault" o = Gtk.Widget.WidgetGetCanDefaultMethodInfo
    ResolvePlugMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolvePlugMethod "getChild" o = Gtk.Bin.BinGetChildMethodInfo
    ResolvePlugMethod "getChildRequisition" o = Gtk.Widget.WidgetGetChildRequisitionMethodInfo
    ResolvePlugMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolvePlugMethod "getChildren" o = Gtk.Container.ContainerGetChildrenMethodInfo
    ResolvePlugMethod "getClip" o = Gtk.Widget.WidgetGetClipMethodInfo
    ResolvePlugMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolvePlugMethod "getCompositeName" o = Gtk.Widget.WidgetGetCompositeNameMethodInfo
    ResolvePlugMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolvePlugMethod "getDecorated" o = Gtk.Window.WindowGetDecoratedMethodInfo
    ResolvePlugMethod "getDefaultSize" o = Gtk.Window.WindowGetDefaultSizeMethodInfo
    ResolvePlugMethod "getDefaultWidget" o = Gtk.Window.WindowGetDefaultWidgetMethodInfo
    ResolvePlugMethod "getDeletable" o = Gtk.Window.WindowGetDeletableMethodInfo
    ResolvePlugMethod "getDestroyWithParent" o = Gtk.Window.WindowGetDestroyWithParentMethodInfo
    ResolvePlugMethod "getDeviceEnabled" o = Gtk.Widget.WidgetGetDeviceEnabledMethodInfo
    ResolvePlugMethod "getDeviceEvents" o = Gtk.Widget.WidgetGetDeviceEventsMethodInfo
    ResolvePlugMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolvePlugMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolvePlugMethod "getDoubleBuffered" o = Gtk.Widget.WidgetGetDoubleBufferedMethodInfo
    ResolvePlugMethod "getEmbedded" o = PlugGetEmbeddedMethodInfo
    ResolvePlugMethod "getEvents" o = Gtk.Widget.WidgetGetEventsMethodInfo
    ResolvePlugMethod "getFocus" o = Gtk.Window.WindowGetFocusMethodInfo
    ResolvePlugMethod "getFocusChain" o = Gtk.Container.ContainerGetFocusChainMethodInfo
    ResolvePlugMethod "getFocusChild" o = Gtk.Container.ContainerGetFocusChildMethodInfo
    ResolvePlugMethod "getFocusHadjustment" o = Gtk.Container.ContainerGetFocusHadjustmentMethodInfo
    ResolvePlugMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolvePlugMethod "getFocusOnMap" o = Gtk.Window.WindowGetFocusOnMapMethodInfo
    ResolvePlugMethod "getFocusVadjustment" o = Gtk.Container.ContainerGetFocusVadjustmentMethodInfo
    ResolvePlugMethod "getFocusVisible" o = Gtk.Window.WindowGetFocusVisibleMethodInfo
    ResolvePlugMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolvePlugMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolvePlugMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolvePlugMethod "getGravity" o = Gtk.Window.WindowGetGravityMethodInfo
    ResolvePlugMethod "getGroup" o = Gtk.Window.WindowGetGroupMethodInfo
    ResolvePlugMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolvePlugMethod "getHasResizeGrip" o = Gtk.Window.WindowGetHasResizeGripMethodInfo
    ResolvePlugMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolvePlugMethod "getHasWindow" o = Gtk.Widget.WidgetGetHasWindowMethodInfo
    ResolvePlugMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolvePlugMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolvePlugMethod "getHideTitlebarWhenMaximized" o = Gtk.Window.WindowGetHideTitlebarWhenMaximizedMethodInfo
    ResolvePlugMethod "getIcon" o = Gtk.Window.WindowGetIconMethodInfo
    ResolvePlugMethod "getIconList" o = Gtk.Window.WindowGetIconListMethodInfo
    ResolvePlugMethod "getIconName" o = Gtk.Window.WindowGetIconNameMethodInfo
    ResolvePlugMethod "getId" o = PlugGetIdMethodInfo
    ResolvePlugMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
    ResolvePlugMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolvePlugMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolvePlugMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolvePlugMethod "getMarginLeft" o = Gtk.Widget.WidgetGetMarginLeftMethodInfo
    ResolvePlugMethod "getMarginRight" o = Gtk.Widget.WidgetGetMarginRightMethodInfo
    ResolvePlugMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolvePlugMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolvePlugMethod "getMnemonicModifier" o = Gtk.Window.WindowGetMnemonicModifierMethodInfo
    ResolvePlugMethod "getMnemonicsVisible" o = Gtk.Window.WindowGetMnemonicsVisibleMethodInfo
    ResolvePlugMethod "getModal" o = Gtk.Window.WindowGetModalMethodInfo
    ResolvePlugMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
    ResolvePlugMethod "getModifierStyle" o = Gtk.Widget.WidgetGetModifierStyleMethodInfo
    ResolvePlugMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolvePlugMethod "getNoShowAll" o = Gtk.Widget.WidgetGetNoShowAllMethodInfo
    ResolvePlugMethod "getOpacity" o = Gtk.Window.WindowGetOpacityMethodInfo
    ResolvePlugMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolvePlugMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolvePlugMethod "getParentWindow" o = Gtk.Widget.WidgetGetParentWindowMethodInfo
    ResolvePlugMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
    ResolvePlugMethod "getPathForChild" o = Gtk.Container.ContainerGetPathForChildMethodInfo
    ResolvePlugMethod "getPointer" o = Gtk.Widget.WidgetGetPointerMethodInfo
    ResolvePlugMethod "getPosition" o = Gtk.Window.WindowGetPositionMethodInfo
    ResolvePlugMethod "getPreferredHeight" o = Gtk.Widget.WidgetGetPreferredHeightMethodInfo
    ResolvePlugMethod "getPreferredHeightAndBaselineForWidth" o = Gtk.Widget.WidgetGetPreferredHeightAndBaselineForWidthMethodInfo
    ResolvePlugMethod "getPreferredHeightForWidth" o = Gtk.Widget.WidgetGetPreferredHeightForWidthMethodInfo
    ResolvePlugMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolvePlugMethod "getPreferredWidth" o = Gtk.Widget.WidgetGetPreferredWidthMethodInfo
    ResolvePlugMethod "getPreferredWidthForHeight" o = Gtk.Widget.WidgetGetPreferredWidthForHeightMethodInfo
    ResolvePlugMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolvePlugMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolvePlugMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolvePlugMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolvePlugMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolvePlugMethod "getRequisition" o = Gtk.Widget.WidgetGetRequisitionMethodInfo
    ResolvePlugMethod "getResizable" o = Gtk.Window.WindowGetResizableMethodInfo
    ResolvePlugMethod "getResizeGripArea" o = Gtk.Window.WindowGetResizeGripAreaMethodInfo
    ResolvePlugMethod "getResizeMode" o = Gtk.Container.ContainerGetResizeModeMethodInfo
    ResolvePlugMethod "getRole" o = Gtk.Window.WindowGetRoleMethodInfo
    ResolvePlugMethod "getRootWindow" o = Gtk.Widget.WidgetGetRootWindowMethodInfo
    ResolvePlugMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolvePlugMethod "getScreen" o = Gtk.Window.WindowGetScreenMethodInfo
    ResolvePlugMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolvePlugMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolvePlugMethod "getSize" o = Gtk.Window.WindowGetSizeMethodInfo
    ResolvePlugMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolvePlugMethod "getSkipPagerHint" o = Gtk.Window.WindowGetSkipPagerHintMethodInfo
    ResolvePlugMethod "getSkipTaskbarHint" o = Gtk.Window.WindowGetSkipTaskbarHintMethodInfo
    ResolvePlugMethod "getSocketWindow" o = PlugGetSocketWindowMethodInfo
    ResolvePlugMethod "getState" o = Gtk.Widget.WidgetGetStateMethodInfo
    ResolvePlugMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolvePlugMethod "getStyle" o = Gtk.Widget.WidgetGetStyleMethodInfo
    ResolvePlugMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolvePlugMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
    ResolvePlugMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolvePlugMethod "getTitle" o = Gtk.Window.WindowGetTitleMethodInfo
    ResolvePlugMethod "getTitlebar" o = Gtk.Window.WindowGetTitlebarMethodInfo
    ResolvePlugMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolvePlugMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolvePlugMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
    ResolvePlugMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
    ResolvePlugMethod "getTransientFor" o = Gtk.Window.WindowGetTransientForMethodInfo
    ResolvePlugMethod "getTypeHint" o = Gtk.Window.WindowGetTypeHintMethodInfo
    ResolvePlugMethod "getUrgencyHint" o = Gtk.Window.WindowGetUrgencyHintMethodInfo
    ResolvePlugMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolvePlugMethod "getValignWithBaseline" o = Gtk.Widget.WidgetGetValignWithBaselineMethodInfo
    ResolvePlugMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolvePlugMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolvePlugMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolvePlugMethod "getVisual" o = Gtk.Widget.WidgetGetVisualMethodInfo
    ResolvePlugMethod "getWindow" o = Gtk.Widget.WidgetGetWindowMethodInfo
    ResolvePlugMethod "getWindowType" o = Gtk.Window.WindowGetWindowTypeMethodInfo
    ResolvePlugMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
    ResolvePlugMethod "setAcceptFocus" o = Gtk.Window.WindowSetAcceptFocusMethodInfo
    ResolvePlugMethod "setAllocation" o = Gtk.Widget.WidgetSetAllocationMethodInfo
    ResolvePlugMethod "setAppPaintable" o = Gtk.Widget.WidgetSetAppPaintableMethodInfo
    ResolvePlugMethod "setApplication" o = Gtk.Window.WindowSetApplicationMethodInfo
    ResolvePlugMethod "setAttachedTo" o = Gtk.Window.WindowSetAttachedToMethodInfo
    ResolvePlugMethod "setBorderWidth" o = Gtk.Container.ContainerSetBorderWidthMethodInfo
    ResolvePlugMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
    ResolvePlugMethod "setCanDefault" o = Gtk.Widget.WidgetSetCanDefaultMethodInfo
    ResolvePlugMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolvePlugMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolvePlugMethod "setClip" o = Gtk.Widget.WidgetSetClipMethodInfo
    ResolvePlugMethod "setCompositeName" o = Gtk.Widget.WidgetSetCompositeNameMethodInfo
    ResolvePlugMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolvePlugMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolvePlugMethod "setDecorated" o = Gtk.Window.WindowSetDecoratedMethodInfo
    ResolvePlugMethod "setDefault" o = Gtk.Window.WindowSetDefaultMethodInfo
    ResolvePlugMethod "setDefaultGeometry" o = Gtk.Window.WindowSetDefaultGeometryMethodInfo
    ResolvePlugMethod "setDefaultSize" o = Gtk.Window.WindowSetDefaultSizeMethodInfo
    ResolvePlugMethod "setDeletable" o = Gtk.Window.WindowSetDeletableMethodInfo
    ResolvePlugMethod "setDestroyWithParent" o = Gtk.Window.WindowSetDestroyWithParentMethodInfo
    ResolvePlugMethod "setDeviceEnabled" o = Gtk.Widget.WidgetSetDeviceEnabledMethodInfo
    ResolvePlugMethod "setDeviceEvents" o = Gtk.Widget.WidgetSetDeviceEventsMethodInfo
    ResolvePlugMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolvePlugMethod "setDoubleBuffered" o = Gtk.Widget.WidgetSetDoubleBufferedMethodInfo
    ResolvePlugMethod "setEvents" o = Gtk.Widget.WidgetSetEventsMethodInfo
    ResolvePlugMethod "setFocus" o = Gtk.Window.WindowSetFocusMethodInfo
    ResolvePlugMethod "setFocusChain" o = Gtk.Container.ContainerSetFocusChainMethodInfo
    ResolvePlugMethod "setFocusChild" o = Gtk.Container.ContainerSetFocusChildMethodInfo
    ResolvePlugMethod "setFocusHadjustment" o = Gtk.Container.ContainerSetFocusHadjustmentMethodInfo
    ResolvePlugMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolvePlugMethod "setFocusOnMap" o = Gtk.Window.WindowSetFocusOnMapMethodInfo
    ResolvePlugMethod "setFocusVadjustment" o = Gtk.Container.ContainerSetFocusVadjustmentMethodInfo
    ResolvePlugMethod "setFocusVisible" o = Gtk.Window.WindowSetFocusVisibleMethodInfo
    ResolvePlugMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolvePlugMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolvePlugMethod "setGeometryHints" o = Gtk.Window.WindowSetGeometryHintsMethodInfo
    ResolvePlugMethod "setGravity" o = Gtk.Window.WindowSetGravityMethodInfo
    ResolvePlugMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolvePlugMethod "setHasResizeGrip" o = Gtk.Window.WindowSetHasResizeGripMethodInfo
    ResolvePlugMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolvePlugMethod "setHasUserRefCount" o = Gtk.Window.WindowSetHasUserRefCountMethodInfo
    ResolvePlugMethod "setHasWindow" o = Gtk.Widget.WidgetSetHasWindowMethodInfo
    ResolvePlugMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolvePlugMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolvePlugMethod "setHideTitlebarWhenMaximized" o = Gtk.Window.WindowSetHideTitlebarWhenMaximizedMethodInfo
    ResolvePlugMethod "setIcon" o = Gtk.Window.WindowSetIconMethodInfo
    ResolvePlugMethod "setIconFromFile" o = Gtk.Window.WindowSetIconFromFileMethodInfo
    ResolvePlugMethod "setIconList" o = Gtk.Window.WindowSetIconListMethodInfo
    ResolvePlugMethod "setIconName" o = Gtk.Window.WindowSetIconNameMethodInfo
    ResolvePlugMethod "setKeepAbove" o = Gtk.Window.WindowSetKeepAboveMethodInfo
    ResolvePlugMethod "setKeepBelow" o = Gtk.Window.WindowSetKeepBelowMethodInfo
    ResolvePlugMethod "setMapped" o = Gtk.Widget.WidgetSetMappedMethodInfo
    ResolvePlugMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolvePlugMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolvePlugMethod "setMarginLeft" o = Gtk.Widget.WidgetSetMarginLeftMethodInfo
    ResolvePlugMethod "setMarginRight" o = Gtk.Widget.WidgetSetMarginRightMethodInfo
    ResolvePlugMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolvePlugMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolvePlugMethod "setMnemonicModifier" o = Gtk.Window.WindowSetMnemonicModifierMethodInfo
    ResolvePlugMethod "setMnemonicsVisible" o = Gtk.Window.WindowSetMnemonicsVisibleMethodInfo
    ResolvePlugMethod "setModal" o = Gtk.Window.WindowSetModalMethodInfo
    ResolvePlugMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolvePlugMethod "setNoShowAll" o = Gtk.Widget.WidgetSetNoShowAllMethodInfo
    ResolvePlugMethod "setOpacity" o = Gtk.Window.WindowSetOpacityMethodInfo
    ResolvePlugMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolvePlugMethod "setParentWindow" o = Gtk.Widget.WidgetSetParentWindowMethodInfo
    ResolvePlugMethod "setPosition" o = Gtk.Window.WindowSetPositionMethodInfo
    ResolvePlugMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolvePlugMethod "setRealized" o = Gtk.Widget.WidgetSetRealizedMethodInfo
    ResolvePlugMethod "setReallocateRedraws" o = Gtk.Container.ContainerSetReallocateRedrawsMethodInfo
    ResolvePlugMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolvePlugMethod "setRedrawOnAllocate" o = Gtk.Widget.WidgetSetRedrawOnAllocateMethodInfo
    ResolvePlugMethod "setResizable" o = Gtk.Window.WindowSetResizableMethodInfo
    ResolvePlugMethod "setResizeMode" o = Gtk.Container.ContainerSetResizeModeMethodInfo
    ResolvePlugMethod "setRole" o = Gtk.Window.WindowSetRoleMethodInfo
    ResolvePlugMethod "setScreen" o = Gtk.Window.WindowSetScreenMethodInfo
    ResolvePlugMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolvePlugMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolvePlugMethod "setSkipPagerHint" o = Gtk.Window.WindowSetSkipPagerHintMethodInfo
    ResolvePlugMethod "setSkipTaskbarHint" o = Gtk.Window.WindowSetSkipTaskbarHintMethodInfo
    ResolvePlugMethod "setStartupId" o = Gtk.Window.WindowSetStartupIdMethodInfo
    ResolvePlugMethod "setState" o = Gtk.Widget.WidgetSetStateMethodInfo
    ResolvePlugMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolvePlugMethod "setStyle" o = Gtk.Widget.WidgetSetStyleMethodInfo
    ResolvePlugMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
    ResolvePlugMethod "setTitle" o = Gtk.Window.WindowSetTitleMethodInfo
    ResolvePlugMethod "setTitlebar" o = Gtk.Window.WindowSetTitlebarMethodInfo
    ResolvePlugMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolvePlugMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolvePlugMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
    ResolvePlugMethod "setTransientFor" o = Gtk.Window.WindowSetTransientForMethodInfo
    ResolvePlugMethod "setTypeHint" o = Gtk.Window.WindowSetTypeHintMethodInfo
    ResolvePlugMethod "setUrgencyHint" o = Gtk.Window.WindowSetUrgencyHintMethodInfo
    ResolvePlugMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolvePlugMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolvePlugMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolvePlugMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolvePlugMethod "setVisual" o = Gtk.Widget.WidgetSetVisualMethodInfo
    ResolvePlugMethod "setWindow" o = Gtk.Widget.WidgetSetWindowMethodInfo
    ResolvePlugMethod "setWmclass" o = Gtk.Window.WindowSetWmclassMethodInfo
    ResolvePlugMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolvePlugMethod t Plug, O.MethodInfo info Plug p) => OL.IsLabel t (Plug -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

-- signal Plug::embedded
-- | Gets emitted when the plug becomes embedded in a socket.
type PlugEmbeddedCallback =
    IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `PlugEmbeddedCallback`@.
noPlugEmbeddedCallback :: Maybe PlugEmbeddedCallback
noPlugEmbeddedCallback :: Maybe (IO ())
noPlugEmbeddedCallback = Maybe (IO ())
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_PlugEmbeddedCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_PlugEmbeddedCallback`.
foreign import ccall "wrapper"
    mk_PlugEmbeddedCallback :: C_PlugEmbeddedCallback -> IO (FunPtr C_PlugEmbeddedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_PlugEmbedded :: MonadIO m => PlugEmbeddedCallback -> m (GClosure C_PlugEmbeddedCallback)
genClosure_PlugEmbedded :: IO () -> m (GClosure C_PlugEmbeddedCallback)
genClosure_PlugEmbedded cb :: IO ()
cb = IO (GClosure C_PlugEmbeddedCallback)
-> m (GClosure C_PlugEmbeddedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_PlugEmbeddedCallback)
 -> m (GClosure C_PlugEmbeddedCallback))
-> IO (GClosure C_PlugEmbeddedCallback)
-> m (GClosure C_PlugEmbeddedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PlugEmbeddedCallback
cb' = IO () -> C_PlugEmbeddedCallback
wrap_PlugEmbeddedCallback IO ()
cb
    C_PlugEmbeddedCallback -> IO (FunPtr C_PlugEmbeddedCallback)
mk_PlugEmbeddedCallback C_PlugEmbeddedCallback
cb' IO (FunPtr C_PlugEmbeddedCallback)
-> (FunPtr C_PlugEmbeddedCallback
    -> IO (GClosure C_PlugEmbeddedCallback))
-> IO (GClosure C_PlugEmbeddedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_PlugEmbeddedCallback
-> IO (GClosure C_PlugEmbeddedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `PlugEmbeddedCallback` into a `C_PlugEmbeddedCallback`.
wrap_PlugEmbeddedCallback ::
    PlugEmbeddedCallback ->
    C_PlugEmbeddedCallback
wrap_PlugEmbeddedCallback :: IO () -> C_PlugEmbeddedCallback
wrap_PlugEmbeddedCallback _cb :: IO ()
_cb _ _ = do
    IO ()
_cb 


-- | Connect a signal handler for the [embedded](#signal:embedded) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' plug #embedded callback
-- @
-- 
-- 
onPlugEmbedded :: (IsPlug a, MonadIO m) => a -> PlugEmbeddedCallback -> m SignalHandlerId
onPlugEmbedded :: a -> IO () -> m SignalHandlerId
onPlugEmbedded obj :: a
obj cb :: IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_PlugEmbeddedCallback
cb' = IO () -> C_PlugEmbeddedCallback
wrap_PlugEmbeddedCallback IO ()
cb
    FunPtr C_PlugEmbeddedCallback
cb'' <- C_PlugEmbeddedCallback -> IO (FunPtr C_PlugEmbeddedCallback)
mk_PlugEmbeddedCallback C_PlugEmbeddedCallback
cb'
    a
-> Text
-> FunPtr C_PlugEmbeddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "embedded" FunPtr C_PlugEmbeddedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [embedded](#signal:embedded) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' plug #embedded callback
-- @
-- 
-- 
afterPlugEmbedded :: (IsPlug a, MonadIO m) => a -> PlugEmbeddedCallback -> m SignalHandlerId
afterPlugEmbedded :: a -> IO () -> m SignalHandlerId
afterPlugEmbedded obj :: a
obj cb :: IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_PlugEmbeddedCallback
cb' = IO () -> C_PlugEmbeddedCallback
wrap_PlugEmbeddedCallback IO ()
cb
    FunPtr C_PlugEmbeddedCallback
cb'' <- C_PlugEmbeddedCallback -> IO (FunPtr C_PlugEmbeddedCallback)
mk_PlugEmbeddedCallback C_PlugEmbeddedCallback
cb'
    a
-> Text
-> FunPtr C_PlugEmbeddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "embedded" FunPtr C_PlugEmbeddedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data PlugEmbeddedSignalInfo
instance SignalInfo PlugEmbeddedSignalInfo where
    type HaskellCallbackType PlugEmbeddedSignalInfo = PlugEmbeddedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_PlugEmbeddedCallback cb
        cb'' <- mk_PlugEmbeddedCallback cb'
        connectSignalFunPtr obj "embedded" cb'' connectMode detail

#endif

-- VVV Prop "embedded"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@embedded@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' plug #embedded
-- @
getPlugEmbedded :: (MonadIO m, IsPlug o) => o -> m Bool
getPlugEmbedded :: o -> m Bool
getPlugEmbedded obj :: o
obj = IO Bool -> m Bool
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
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "embedded"

#if defined(ENABLE_OVERLOADING)
data PlugEmbeddedPropertyInfo
instance AttrInfo PlugEmbeddedPropertyInfo where
    type AttrAllowedOps PlugEmbeddedPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint PlugEmbeddedPropertyInfo = IsPlug
    type AttrSetTypeConstraint PlugEmbeddedPropertyInfo = (~) ()
    type AttrTransferTypeConstraint PlugEmbeddedPropertyInfo = (~) ()
    type AttrTransferType PlugEmbeddedPropertyInfo = ()
    type AttrGetType PlugEmbeddedPropertyInfo = Bool
    type AttrLabel PlugEmbeddedPropertyInfo = "embedded"
    type AttrOrigin PlugEmbeddedPropertyInfo = Plug
    attrGet = getPlugEmbedded
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "socket-window"
   -- Type: TInterface (Name {namespace = "Gdk", name = "Window"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Just True,Nothing)

-- | Get the value of the “@socket-window@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' plug #socketWindow
-- @
getPlugSocketWindow :: (MonadIO m, IsPlug o) => o -> m (Maybe Gdk.Window.Window)
getPlugSocketWindow :: o -> m (Maybe Window)
getPlugSocketWindow obj :: o
obj = IO (Maybe Window) -> m (Maybe Window)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Window) -> m (Maybe Window))
-> IO (Maybe Window) -> m (Maybe Window)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Window -> Window) -> IO (Maybe Window)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "socket-window" ManagedPtr Window -> Window
Gdk.Window.Window

#if defined(ENABLE_OVERLOADING)
data PlugSocketWindowPropertyInfo
instance AttrInfo PlugSocketWindowPropertyInfo where
    type AttrAllowedOps PlugSocketWindowPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint PlugSocketWindowPropertyInfo = IsPlug
    type AttrSetTypeConstraint PlugSocketWindowPropertyInfo = (~) ()
    type AttrTransferTypeConstraint PlugSocketWindowPropertyInfo = (~) ()
    type AttrTransferType PlugSocketWindowPropertyInfo = ()
    type AttrGetType PlugSocketWindowPropertyInfo = (Maybe Gdk.Window.Window)
    type AttrLabel PlugSocketWindowPropertyInfo = "socket-window"
    type AttrOrigin PlugSocketWindowPropertyInfo = Plug
    attrGet = getPlugSocketWindow
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Plug
type instance O.AttributeList Plug = PlugAttributeList
type PlugAttributeList = ('[ '("acceptFocus", Gtk.Window.WindowAcceptFocusPropertyInfo), '("appPaintable", Gtk.Widget.WidgetAppPaintablePropertyInfo), '("application", Gtk.Window.WindowApplicationPropertyInfo), '("attachedTo", Gtk.Window.WindowAttachedToPropertyInfo), '("borderWidth", Gtk.Container.ContainerBorderWidthPropertyInfo), '("canDefault", Gtk.Widget.WidgetCanDefaultPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("child", Gtk.Container.ContainerChildPropertyInfo), '("compositeChild", Gtk.Widget.WidgetCompositeChildPropertyInfo), '("decorated", Gtk.Window.WindowDecoratedPropertyInfo), '("defaultHeight", Gtk.Window.WindowDefaultHeightPropertyInfo), '("defaultWidth", Gtk.Window.WindowDefaultWidthPropertyInfo), '("deletable", Gtk.Window.WindowDeletablePropertyInfo), '("destroyWithParent", Gtk.Window.WindowDestroyWithParentPropertyInfo), '("doubleBuffered", Gtk.Widget.WidgetDoubleBufferedPropertyInfo), '("embedded", PlugEmbeddedPropertyInfo), '("events", Gtk.Widget.WidgetEventsPropertyInfo), '("expand", Gtk.Widget.WidgetExpandPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("focusOnMap", Gtk.Window.WindowFocusOnMapPropertyInfo), '("focusVisible", Gtk.Window.WindowFocusVisiblePropertyInfo), '("gravity", Gtk.Window.WindowGravityPropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasResizeGrip", Gtk.Window.WindowHasResizeGripPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("hasToplevelFocus", Gtk.Window.WindowHasToplevelFocusPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("hideTitlebarWhenMaximized", Gtk.Window.WindowHideTitlebarWhenMaximizedPropertyInfo), '("icon", Gtk.Window.WindowIconPropertyInfo), '("iconName", Gtk.Window.WindowIconNamePropertyInfo), '("isActive", Gtk.Window.WindowIsActivePropertyInfo), '("isFocus", Gtk.Widget.WidgetIsFocusPropertyInfo), '("isMaximized", Gtk.Window.WindowIsMaximizedPropertyInfo), '("margin", Gtk.Widget.WidgetMarginPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginLeft", Gtk.Widget.WidgetMarginLeftPropertyInfo), '("marginRight", Gtk.Widget.WidgetMarginRightPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("mnemonicsVisible", Gtk.Window.WindowMnemonicsVisiblePropertyInfo), '("modal", Gtk.Window.WindowModalPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("noShowAll", Gtk.Widget.WidgetNoShowAllPropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("resizable", Gtk.Window.WindowResizablePropertyInfo), '("resizeGripVisible", Gtk.Window.WindowResizeGripVisiblePropertyInfo), '("resizeMode", Gtk.Container.ContainerResizeModePropertyInfo), '("role", Gtk.Window.WindowRolePropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("screen", Gtk.Window.WindowScreenPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("skipPagerHint", Gtk.Window.WindowSkipPagerHintPropertyInfo), '("skipTaskbarHint", Gtk.Window.WindowSkipTaskbarHintPropertyInfo), '("socketWindow", PlugSocketWindowPropertyInfo), '("startupId", Gtk.Window.WindowStartupIdPropertyInfo), '("style", Gtk.Widget.WidgetStylePropertyInfo), '("title", Gtk.Window.WindowTitlePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("transientFor", Gtk.Window.WindowTransientForPropertyInfo), '("type", Gtk.Window.WindowTypePropertyInfo), '("typeHint", Gtk.Window.WindowTypeHintPropertyInfo), '("urgencyHint", Gtk.Window.WindowUrgencyHintPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo), '("window", Gtk.Widget.WidgetWindowPropertyInfo), '("windowPosition", Gtk.Window.WindowWindowPositionPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
plugEmbedded :: AttrLabelProxy "embedded"
plugEmbedded = AttrLabelProxy

plugSocketWindow :: AttrLabelProxy "socketWindow"
plugSocketWindow = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Plug = PlugSignalList
type PlugSignalList = ('[ '("accelClosuresChanged", Gtk.Widget.WidgetAccelClosuresChangedSignalInfo), '("activateDefault", Gtk.Window.WindowActivateDefaultSignalInfo), '("activateFocus", Gtk.Window.WindowActivateFocusSignalInfo), '("add", Gtk.Container.ContainerAddSignalInfo), '("buttonPressEvent", Gtk.Widget.WidgetButtonPressEventSignalInfo), '("buttonReleaseEvent", Gtk.Widget.WidgetButtonReleaseEventSignalInfo), '("canActivateAccel", Gtk.Widget.WidgetCanActivateAccelSignalInfo), '("checkResize", Gtk.Container.ContainerCheckResizeSignalInfo), '("childNotify", Gtk.Widget.WidgetChildNotifySignalInfo), '("compositedChanged", Gtk.Widget.WidgetCompositedChangedSignalInfo), '("configureEvent", Gtk.Widget.WidgetConfigureEventSignalInfo), '("damageEvent", Gtk.Widget.WidgetDamageEventSignalInfo), '("deleteEvent", Gtk.Widget.WidgetDeleteEventSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("destroyEvent", Gtk.Widget.WidgetDestroyEventSignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("dragBegin", Gtk.Widget.WidgetDragBeginSignalInfo), '("dragDataDelete", Gtk.Widget.WidgetDragDataDeleteSignalInfo), '("dragDataGet", Gtk.Widget.WidgetDragDataGetSignalInfo), '("dragDataReceived", Gtk.Widget.WidgetDragDataReceivedSignalInfo), '("dragDrop", Gtk.Widget.WidgetDragDropSignalInfo), '("dragEnd", Gtk.Widget.WidgetDragEndSignalInfo), '("dragFailed", Gtk.Widget.WidgetDragFailedSignalInfo), '("dragLeave", Gtk.Widget.WidgetDragLeaveSignalInfo), '("dragMotion", Gtk.Widget.WidgetDragMotionSignalInfo), '("draw", Gtk.Widget.WidgetDrawSignalInfo), '("embedded", PlugEmbeddedSignalInfo), '("enableDebugging", Gtk.Window.WindowEnableDebuggingSignalInfo), '("enterNotifyEvent", Gtk.Widget.WidgetEnterNotifyEventSignalInfo), '("event", Gtk.Widget.WidgetEventSignalInfo), '("eventAfter", Gtk.Widget.WidgetEventAfterSignalInfo), '("focus", Gtk.Widget.WidgetFocusSignalInfo), '("focusInEvent", Gtk.Widget.WidgetFocusInEventSignalInfo), '("focusOutEvent", Gtk.Widget.WidgetFocusOutEventSignalInfo), '("grabBrokenEvent", Gtk.Widget.WidgetGrabBrokenEventSignalInfo), '("grabFocus", Gtk.Widget.WidgetGrabFocusSignalInfo), '("grabNotify", Gtk.Widget.WidgetGrabNotifySignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("hierarchyChanged", Gtk.Widget.WidgetHierarchyChangedSignalInfo), '("keyPressEvent", Gtk.Widget.WidgetKeyPressEventSignalInfo), '("keyReleaseEvent", Gtk.Widget.WidgetKeyReleaseEventSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("keysChanged", Gtk.Window.WindowKeysChangedSignalInfo), '("leaveNotifyEvent", Gtk.Widget.WidgetLeaveNotifyEventSignalInfo), '("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), '("setFocus", Gtk.Window.WindowSetFocusSignalInfo), '("setFocusChild", Gtk.Container.ContainerSetFocusChildSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("showHelp", Gtk.Widget.WidgetShowHelpSignalInfo), '("sizeAllocate", Gtk.Widget.WidgetSizeAllocateSignalInfo), '("stateChanged", Gtk.Widget.WidgetStateChangedSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("styleSet", Gtk.Widget.WidgetStyleSetSignalInfo), '("styleUpdated", Gtk.Widget.WidgetStyleUpdatedSignalInfo), '("touchEvent", Gtk.Widget.WidgetTouchEventSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unmapEvent", Gtk.Widget.WidgetUnmapEventSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo), '("visibilityNotifyEvent", Gtk.Widget.WidgetVisibilityNotifyEventSignalInfo), '("windowStateEvent", Gtk.Widget.WidgetWindowStateEventSignalInfo)] :: [(Symbol, *)])

#endif

-- method Plug::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "socket_id"
--           , argType = TBasicType TULong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the window ID of the socket, or 0."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Plug" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_plug_new" gtk_plug_new :: 
    CULong ->                               -- socket_id : TBasicType TULong
    IO (Ptr Plug)

-- | Creates a new plug widget inside the t'GI.Gtk.Objects.Socket.Socket' identified
-- by /@socketId@/. If /@socketId@/ is 0, the plug is left “unplugged” and
-- can later be plugged into a t'GI.Gtk.Objects.Socket.Socket' by  'GI.Gtk.Objects.Socket.socketAddId'.
plugNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    CULong
    -- ^ /@socketId@/: the window ID of the socket, or 0.
    -> m Plug
    -- ^ __Returns:__ the new t'GI.Gtk.Objects.Plug.Plug' widget.
plugNew :: SignalHandlerId -> m Plug
plugNew socketId :: SignalHandlerId
socketId = IO Plug -> m Plug
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Plug -> m Plug) -> IO Plug -> m Plug
forall a b. (a -> b) -> a -> b
$ do
    Ptr Plug
result <- SignalHandlerId -> IO (Ptr Plug)
gtk_plug_new SignalHandlerId
socketId
    Text -> Ptr Plug -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "plugNew" Ptr Plug
result
    Plug
result' <- ((ManagedPtr Plug -> Plug) -> Ptr Plug -> IO Plug
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Plug -> Plug
Plug) Ptr Plug
result
    Plug -> IO Plug
forall (m :: * -> *) a. Monad m => a -> m a
return Plug
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Plug::new_for_display
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "display"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Display" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the #GdkDisplay on which @socket_id is displayed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "socket_id"
--           , argType = TBasicType TULong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the XID of the socket\8217s window."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Plug" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_plug_new_for_display" gtk_plug_new_for_display :: 
    Ptr Gdk.Display.Display ->              -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    CULong ->                               -- socket_id : TBasicType TULong
    IO (Ptr Plug)

-- | Create a new plug widget inside the t'GI.Gtk.Objects.Socket.Socket' identified by socket_id.
-- 
-- /Since: 2.2/
plugNewForDisplay ::
    (B.CallStack.HasCallStack, MonadIO m, Gdk.Display.IsDisplay a) =>
    a
    -- ^ /@display@/: the t'GI.Gdk.Objects.Display.Display' on which /@socketId@/ is displayed
    -> CULong
    -- ^ /@socketId@/: the XID of the socket’s window.
    -> m Plug
    -- ^ __Returns:__ the new t'GI.Gtk.Objects.Plug.Plug' widget.
plugNewForDisplay :: a -> SignalHandlerId -> m Plug
plugNewForDisplay display :: a
display socketId :: SignalHandlerId
socketId = IO Plug -> m Plug
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Plug -> m Plug) -> IO Plug -> m Plug
forall a b. (a -> b) -> a -> b
$ do
    Ptr Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
    Ptr Plug
result <- Ptr Display -> SignalHandlerId -> IO (Ptr Plug)
gtk_plug_new_for_display Ptr Display
display' SignalHandlerId
socketId
    Text -> Ptr Plug -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "plugNewForDisplay" Ptr Plug
result
    Plug
result' <- ((ManagedPtr Plug -> Plug) -> Ptr Plug -> IO Plug
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Plug -> Plug
Plug) Ptr Plug
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
    Plug -> IO Plug
forall (m :: * -> *) a. Monad m => a -> m a
return Plug
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Plug::construct
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "plug"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Plug" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPlug." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "socket_id"
--           , argType = TBasicType TULong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the XID of the socket\8217s window."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_plug_construct" gtk_plug_construct :: 
    Ptr Plug ->                             -- plug : TInterface (Name {namespace = "Gtk", name = "Plug"})
    CULong ->                               -- socket_id : TBasicType TULong
    IO ()

-- | Finish the initialization of /@plug@/ for a given t'GI.Gtk.Objects.Socket.Socket' identified by
-- /@socketId@/. This function will generally only be used by classes deriving from t'GI.Gtk.Objects.Plug.Plug'.
plugConstruct ::
    (B.CallStack.HasCallStack, MonadIO m, IsPlug a) =>
    a
    -- ^ /@plug@/: a t'GI.Gtk.Objects.Plug.Plug'.
    -> CULong
    -- ^ /@socketId@/: the XID of the socket’s window.
    -> m ()
plugConstruct :: a -> SignalHandlerId -> m ()
plugConstruct plug :: a
plug socketId :: SignalHandlerId
socketId = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Plug
plug' <- a -> IO (Ptr Plug)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
plug
    Ptr Plug -> SignalHandlerId -> IO ()
gtk_plug_construct Ptr Plug
plug' SignalHandlerId
socketId
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
plug
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PlugConstructMethodInfo
instance (signature ~ (CULong -> m ()), MonadIO m, IsPlug a) => O.MethodInfo PlugConstructMethodInfo a signature where
    overloadedMethod = plugConstruct

#endif

-- method Plug::construct_for_display
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "plug"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Plug" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPlug." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "display"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Display" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the #GdkDisplay associated with @socket_id\8217s\n     #GtkSocket."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "socket_id"
--           , argType = TBasicType TULong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the XID of the socket\8217s window."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_plug_construct_for_display" gtk_plug_construct_for_display :: 
    Ptr Plug ->                             -- plug : TInterface (Name {namespace = "Gtk", name = "Plug"})
    Ptr Gdk.Display.Display ->              -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    CULong ->                               -- socket_id : TBasicType TULong
    IO ()

-- | Finish the initialization of /@plug@/ for a given t'GI.Gtk.Objects.Socket.Socket' identified by
-- /@socketId@/ which is currently displayed on /@display@/.
-- This function will generally only be used by classes deriving from t'GI.Gtk.Objects.Plug.Plug'.
-- 
-- /Since: 2.2/
plugConstructForDisplay ::
    (B.CallStack.HasCallStack, MonadIO m, IsPlug a, Gdk.Display.IsDisplay b) =>
    a
    -- ^ /@plug@/: a t'GI.Gtk.Objects.Plug.Plug'.
    -> b
    -- ^ /@display@/: the t'GI.Gdk.Objects.Display.Display' associated with /@socketId@/’s
    --      t'GI.Gtk.Objects.Socket.Socket'.
    -> CULong
    -- ^ /@socketId@/: the XID of the socket’s window.
    -> m ()
plugConstructForDisplay :: a -> b -> SignalHandlerId -> m ()
plugConstructForDisplay plug :: a
plug display :: b
display socketId :: SignalHandlerId
socketId = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Plug
plug' <- a -> IO (Ptr Plug)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
plug
    Ptr Display
display' <- b -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
display
    Ptr Plug -> Ptr Display -> SignalHandlerId -> IO ()
gtk_plug_construct_for_display Ptr Plug
plug' Ptr Display
display' SignalHandlerId
socketId
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
plug
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
display
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PlugConstructForDisplayMethodInfo
instance (signature ~ (b -> CULong -> m ()), MonadIO m, IsPlug a, Gdk.Display.IsDisplay b) => O.MethodInfo PlugConstructForDisplayMethodInfo a signature where
    overloadedMethod = plugConstructForDisplay

#endif

-- method Plug::get_embedded
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "plug"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Plug" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPlug" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_plug_get_embedded" gtk_plug_get_embedded :: 
    Ptr Plug ->                             -- plug : TInterface (Name {namespace = "Gtk", name = "Plug"})
    IO CInt

-- | Determines whether the plug is embedded in a socket.
-- 
-- /Since: 2.14/
plugGetEmbedded ::
    (B.CallStack.HasCallStack, MonadIO m, IsPlug a) =>
    a
    -- ^ /@plug@/: a t'GI.Gtk.Objects.Plug.Plug'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the plug is embedded in a socket
plugGetEmbedded :: a -> m Bool
plugGetEmbedded plug :: a
plug = IO Bool -> m Bool
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 Plug
plug' <- a -> IO (Ptr Plug)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
plug
    CInt
result <- Ptr Plug -> IO CInt
gtk_plug_get_embedded Ptr Plug
plug'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
plug
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data PlugGetEmbeddedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPlug a) => O.MethodInfo PlugGetEmbeddedMethodInfo a signature where
    overloadedMethod = plugGetEmbedded

#endif

-- method Plug::get_id
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "plug"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Plug" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPlug." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TULong)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_plug_get_id" gtk_plug_get_id :: 
    Ptr Plug ->                             -- plug : TInterface (Name {namespace = "Gtk", name = "Plug"})
    IO CULong

-- | Gets the window ID of a t'GI.Gtk.Objects.Plug.Plug' widget, which can then
-- be used to embed this window inside another window, for
-- instance with 'GI.Gtk.Objects.Socket.socketAddId'.
plugGetId ::
    (B.CallStack.HasCallStack, MonadIO m, IsPlug a) =>
    a
    -- ^ /@plug@/: a t'GI.Gtk.Objects.Plug.Plug'.
    -> m CULong
    -- ^ __Returns:__ the window ID for the plug
plugGetId :: a -> m SignalHandlerId
plugGetId plug :: a
plug = IO SignalHandlerId -> m SignalHandlerId
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
    Ptr Plug
plug' <- a -> IO (Ptr Plug)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
plug
    SignalHandlerId
result <- Ptr Plug -> IO SignalHandlerId
gtk_plug_get_id Ptr Plug
plug'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
plug
    SignalHandlerId -> IO SignalHandlerId
forall (m :: * -> *) a. Monad m => a -> m a
return SignalHandlerId
result

#if defined(ENABLE_OVERLOADING)
data PlugGetIdMethodInfo
instance (signature ~ (m CULong), MonadIO m, IsPlug a) => O.MethodInfo PlugGetIdMethodInfo a signature where
    overloadedMethod = plugGetId

#endif

-- method Plug::get_socket_window
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "plug"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Plug" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPlug" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Window" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_plug_get_socket_window" gtk_plug_get_socket_window :: 
    Ptr Plug ->                             -- plug : TInterface (Name {namespace = "Gtk", name = "Plug"})
    IO (Ptr Gdk.Window.Window)

-- | Retrieves the socket the plug is embedded in.
-- 
-- /Since: 2.14/
plugGetSocketWindow ::
    (B.CallStack.HasCallStack, MonadIO m, IsPlug a) =>
    a
    -- ^ /@plug@/: a t'GI.Gtk.Objects.Plug.Plug'
    -> m (Maybe Gdk.Window.Window)
    -- ^ __Returns:__ the window of the socket, or 'P.Nothing'
plugGetSocketWindow :: a -> m (Maybe Window)
plugGetSocketWindow plug :: a
plug = IO (Maybe Window) -> m (Maybe Window)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Window) -> m (Maybe Window))
-> IO (Maybe Window) -> m (Maybe Window)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Plug
plug' <- a -> IO (Ptr Plug)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
plug
    Ptr Window
result <- Ptr Plug -> IO (Ptr Window)
gtk_plug_get_socket_window Ptr Plug
plug'
    Maybe Window
maybeResult <- Ptr Window -> (Ptr Window -> IO Window) -> IO (Maybe Window)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Window
result ((Ptr Window -> IO Window) -> IO (Maybe Window))
-> (Ptr Window -> IO Window) -> IO (Maybe Window)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr Window
result' -> do
        Window
result'' <- ((ManagedPtr Window -> Window) -> Ptr Window -> IO Window
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Window -> Window
Gdk.Window.Window) Ptr Window
result'
        Window -> IO Window
forall (m :: * -> *) a. Monad m => a -> m a
return Window
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
plug
    Maybe Window -> IO (Maybe Window)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Window
maybeResult

#if defined(ENABLE_OVERLOADING)
data PlugGetSocketWindowMethodInfo
instance (signature ~ (m (Maybe Gdk.Window.Window)), MonadIO m, IsPlug a) => O.MethodInfo PlugGetSocketWindowMethodInfo a signature where
    overloadedMethod = plugGetSocketWindow

#endif