{-# 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.Plug.Plug', t'GI.Gtk.Objects.Socket.Socket' 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 that widget’s window ID 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 socket’s window ID is obtained by using 'GI.Gtk.Objects.Socket.socketGetId'.
-- Before using this function, the socket must have been realized,
-- and for hence, have been added to its parent.
-- 
-- == Obtaining the window ID of a socket.
-- 
-- 
-- === /C code/
-- >
-- >GtkWidget *socket = gtk_socket_new ();
-- >gtk_widget_show (socket);
-- >gtk_container_add (GTK_CONTAINER (parent), socket);
-- >
-- >// The following call is only necessary if one of
-- >// the ancestors of the socket is not yet visible.
-- >gtk_widget_realize (socket);
-- >g_print ("The ID of the sockets window is %#x\n",
-- >         gtk_socket_get_id (socket));
-- 
-- 
-- Note that if you pass the window ID of the socket to another
-- process that will create a plug in the socket, you must make
-- sure that the socket widget is not destroyed until that plug
-- is created. Violating this rule will cause unpredictable
-- consequences, the most likely consequence being that the plug
-- will appear as a separate toplevel window. You can check if
-- the plug has been created by using 'GI.Gtk.Objects.Socket.socketGetPlugWindow'.
-- If it returns a non-'P.Nothing' value, then the plug has been
-- successfully created inside of the socket.
-- 
-- When GTK+ is notified that the embedded window has been destroyed,
-- then it will destroy the socket as well. You should always,
-- therefore, be prepared for your sockets to be destroyed at any
-- time when the main event loop is running. To prevent this from
-- happening, you can connect to the [plugRemoved]("GI.Gtk.Objects.Socket#signal:plugRemoved") signal.
-- 
-- 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.Socket
    ( 

-- * Exported types
    Socket(..)                              ,
    IsSocket                                ,
    toSocket                                ,
    noSocket                                ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveSocketMethod                     ,
#endif


-- ** addId #method:addId#

#if defined(ENABLE_OVERLOADING)
    SocketAddIdMethodInfo                   ,
#endif
    socketAddId                             ,


-- ** getId #method:getId#

#if defined(ENABLE_OVERLOADING)
    SocketGetIdMethodInfo                   ,
#endif
    socketGetId                             ,


-- ** getPlugWindow #method:getPlugWindow#

#if defined(ENABLE_OVERLOADING)
    SocketGetPlugWindowMethodInfo           ,
#endif
    socketGetPlugWindow                     ,


-- ** new #method:new#

    socketNew                               ,




 -- * Signals
-- ** plugAdded #signal:plugAdded#

    C_SocketPlugAddedCallback               ,
    SocketPlugAddedCallback                 ,
#if defined(ENABLE_OVERLOADING)
    SocketPlugAddedSignalInfo               ,
#endif
    afterSocketPlugAdded                    ,
    genClosure_SocketPlugAdded              ,
    mk_SocketPlugAddedCallback              ,
    noSocketPlugAddedCallback               ,
    onSocketPlugAdded                       ,
    wrap_SocketPlugAddedCallback            ,


-- ** plugRemoved #signal:plugRemoved#

    C_SocketPlugRemovedCallback             ,
    SocketPlugRemovedCallback               ,
#if defined(ENABLE_OVERLOADING)
    SocketPlugRemovedSignalInfo             ,
#endif
    afterSocketPlugRemoved                  ,
    genClosure_SocketPlugRemoved            ,
    mk_SocketPlugRemovedCallback            ,
    noSocketPlugRemovedCallback             ,
    onSocketPlugRemoved                     ,
    wrap_SocketPlugRemovedCallback          ,




    ) 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.Window as Gdk.Window
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Objects.Container as Gtk.Container
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget

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

instance GObject Socket where
    gobjectType :: IO GType
gobjectType = IO GType
c_gtk_socket_get_type
    

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

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

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

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

-- | A convenience alias for `Nothing` :: `Maybe` `Socket`.
noSocket :: Maybe Socket
noSocket :: Maybe Socket
noSocket = Maybe Socket
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveSocketMethod (t :: Symbol) (o :: *) :: * where
    ResolveSocketMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveSocketMethod "add" o = Gtk.Container.ContainerAddMethodInfo
    ResolveSocketMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
    ResolveSocketMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
    ResolveSocketMethod "addDeviceEvents" o = Gtk.Widget.WidgetAddDeviceEventsMethodInfo
    ResolveSocketMethod "addEvents" o = Gtk.Widget.WidgetAddEventsMethodInfo
    ResolveSocketMethod "addId" o = SocketAddIdMethodInfo
    ResolveSocketMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveSocketMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveSocketMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveSocketMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveSocketMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
    ResolveSocketMethod "checkResize" o = Gtk.Container.ContainerCheckResizeMethodInfo
    ResolveSocketMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveSocketMethod "childGetProperty" o = Gtk.Container.ContainerChildGetPropertyMethodInfo
    ResolveSocketMethod "childNotify" o = Gtk.Container.ContainerChildNotifyMethodInfo
    ResolveSocketMethod "childNotifyByPspec" o = Gtk.Container.ContainerChildNotifyByPspecMethodInfo
    ResolveSocketMethod "childSetProperty" o = Gtk.Container.ContainerChildSetPropertyMethodInfo
    ResolveSocketMethod "childType" o = Gtk.Container.ContainerChildTypeMethodInfo
    ResolveSocketMethod "classPath" o = Gtk.Widget.WidgetClassPathMethodInfo
    ResolveSocketMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveSocketMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
    ResolveSocketMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveSocketMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveSocketMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
    ResolveSocketMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
    ResolveSocketMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
    ResolveSocketMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
    ResolveSocketMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
    ResolveSocketMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
    ResolveSocketMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
    ResolveSocketMethod "dragBeginWithCoordinates" o = Gtk.Widget.WidgetDragBeginWithCoordinatesMethodInfo
    ResolveSocketMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveSocketMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
    ResolveSocketMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
    ResolveSocketMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
    ResolveSocketMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
    ResolveSocketMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
    ResolveSocketMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
    ResolveSocketMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
    ResolveSocketMethod "dragDestSetProxy" o = Gtk.Widget.WidgetDragDestSetProxyMethodInfo
    ResolveSocketMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
    ResolveSocketMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
    ResolveSocketMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
    ResolveSocketMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
    ResolveSocketMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
    ResolveSocketMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
    ResolveSocketMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
    ResolveSocketMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
    ResolveSocketMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
    ResolveSocketMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
    ResolveSocketMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
    ResolveSocketMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
    ResolveSocketMethod "dragSourceSetIconPixbuf" o = Gtk.Widget.WidgetDragSourceSetIconPixbufMethodInfo
    ResolveSocketMethod "dragSourceSetIconStock" o = Gtk.Widget.WidgetDragSourceSetIconStockMethodInfo
    ResolveSocketMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
    ResolveSocketMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
    ResolveSocketMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
    ResolveSocketMethod "draw" o = Gtk.Widget.WidgetDrawMethodInfo
    ResolveSocketMethod "ensureStyle" o = Gtk.Widget.WidgetEnsureStyleMethodInfo
    ResolveSocketMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveSocketMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
    ResolveSocketMethod "forall" o = Gtk.Container.ContainerForallMethodInfo
    ResolveSocketMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveSocketMethod "foreach" o = Gtk.Container.ContainerForeachMethodInfo
    ResolveSocketMethod "freezeChildNotify" o = Gtk.Widget.WidgetFreezeChildNotifyMethodInfo
    ResolveSocketMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveSocketMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveSocketMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
    ResolveSocketMethod "grabDefault" o = Gtk.Widget.WidgetGrabDefaultMethodInfo
    ResolveSocketMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveSocketMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
    ResolveSocketMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveSocketMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveSocketMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
    ResolveSocketMethod "hasRcStyle" o = Gtk.Widget.WidgetHasRcStyleMethodInfo
    ResolveSocketMethod "hasScreen" o = Gtk.Widget.WidgetHasScreenMethodInfo
    ResolveSocketMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveSocketMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveSocketMethod "hideOnDelete" o = Gtk.Widget.WidgetHideOnDeleteMethodInfo
    ResolveSocketMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveSocketMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveSocketMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
    ResolveSocketMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveSocketMethod "intersect" o = Gtk.Widget.WidgetIntersectMethodInfo
    ResolveSocketMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveSocketMethod "isComposited" o = Gtk.Widget.WidgetIsCompositedMethodInfo
    ResolveSocketMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolveSocketMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveSocketMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolveSocketMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolveSocketMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
    ResolveSocketMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveSocketMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveSocketMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
    ResolveSocketMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
    ResolveSocketMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveSocketMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveSocketMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveSocketMethod "modifyBase" o = Gtk.Widget.WidgetModifyBaseMethodInfo
    ResolveSocketMethod "modifyBg" o = Gtk.Widget.WidgetModifyBgMethodInfo
    ResolveSocketMethod "modifyCursor" o = Gtk.Widget.WidgetModifyCursorMethodInfo
    ResolveSocketMethod "modifyFg" o = Gtk.Widget.WidgetModifyFgMethodInfo
    ResolveSocketMethod "modifyFont" o = Gtk.Widget.WidgetModifyFontMethodInfo
    ResolveSocketMethod "modifyStyle" o = Gtk.Widget.WidgetModifyStyleMethodInfo
    ResolveSocketMethod "modifyText" o = Gtk.Widget.WidgetModifyTextMethodInfo
    ResolveSocketMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveSocketMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveSocketMethod "overrideBackgroundColor" o = Gtk.Widget.WidgetOverrideBackgroundColorMethodInfo
    ResolveSocketMethod "overrideColor" o = Gtk.Widget.WidgetOverrideColorMethodInfo
    ResolveSocketMethod "overrideCursor" o = Gtk.Widget.WidgetOverrideCursorMethodInfo
    ResolveSocketMethod "overrideFont" o = Gtk.Widget.WidgetOverrideFontMethodInfo
    ResolveSocketMethod "overrideSymbolicColor" o = Gtk.Widget.WidgetOverrideSymbolicColorMethodInfo
    ResolveSocketMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
    ResolveSocketMethod "path" o = Gtk.Widget.WidgetPathMethodInfo
    ResolveSocketMethod "propagateDraw" o = Gtk.Container.ContainerPropagateDrawMethodInfo
    ResolveSocketMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveSocketMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
    ResolveSocketMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveSocketMethod "queueDrawArea" o = Gtk.Widget.WidgetQueueDrawAreaMethodInfo
    ResolveSocketMethod "queueDrawRegion" o = Gtk.Widget.WidgetQueueDrawRegionMethodInfo
    ResolveSocketMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveSocketMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
    ResolveSocketMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveSocketMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveSocketMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveSocketMethod "regionIntersect" o = Gtk.Widget.WidgetRegionIntersectMethodInfo
    ResolveSocketMethod "registerWindow" o = Gtk.Widget.WidgetRegisterWindowMethodInfo
    ResolveSocketMethod "remove" o = Gtk.Container.ContainerRemoveMethodInfo
    ResolveSocketMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
    ResolveSocketMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveSocketMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveSocketMethod "renderIcon" o = Gtk.Widget.WidgetRenderIconMethodInfo
    ResolveSocketMethod "renderIconPixbuf" o = Gtk.Widget.WidgetRenderIconPixbufMethodInfo
    ResolveSocketMethod "reparent" o = Gtk.Widget.WidgetReparentMethodInfo
    ResolveSocketMethod "resetRcStyles" o = Gtk.Widget.WidgetResetRcStylesMethodInfo
    ResolveSocketMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
    ResolveSocketMethod "resizeChildren" o = Gtk.Container.ContainerResizeChildrenMethodInfo
    ResolveSocketMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveSocketMethod "sendExpose" o = Gtk.Widget.WidgetSendExposeMethodInfo
    ResolveSocketMethod "sendFocusChange" o = Gtk.Widget.WidgetSendFocusChangeMethodInfo
    ResolveSocketMethod "shapeCombineRegion" o = Gtk.Widget.WidgetShapeCombineRegionMethodInfo
    ResolveSocketMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveSocketMethod "showAll" o = Gtk.Widget.WidgetShowAllMethodInfo
    ResolveSocketMethod "showNow" o = Gtk.Widget.WidgetShowNowMethodInfo
    ResolveSocketMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveSocketMethod "sizeAllocateWithBaseline" o = Gtk.Widget.WidgetSizeAllocateWithBaselineMethodInfo
    ResolveSocketMethod "sizeRequest" o = Gtk.Widget.WidgetSizeRequestMethodInfo
    ResolveSocketMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveSocketMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveSocketMethod "styleAttach" o = Gtk.Widget.WidgetStyleAttachMethodInfo
    ResolveSocketMethod "styleGetProperty" o = Gtk.Widget.WidgetStyleGetPropertyMethodInfo
    ResolveSocketMethod "thawChildNotify" o = Gtk.Widget.WidgetThawChildNotifyMethodInfo
    ResolveSocketMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveSocketMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolveSocketMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolveSocketMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolveSocketMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolveSocketMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolveSocketMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveSocketMethod "unregisterWindow" o = Gtk.Widget.WidgetUnregisterWindowMethodInfo
    ResolveSocketMethod "unsetFocusChain" o = Gtk.Container.ContainerUnsetFocusChainMethodInfo
    ResolveSocketMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveSocketMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveSocketMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
    ResolveSocketMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
    ResolveSocketMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveSocketMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveSocketMethod "getAllocatedSize" o = Gtk.Widget.WidgetGetAllocatedSizeMethodInfo
    ResolveSocketMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveSocketMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveSocketMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveSocketMethod "getAppPaintable" o = Gtk.Widget.WidgetGetAppPaintableMethodInfo
    ResolveSocketMethod "getBorderWidth" o = Gtk.Container.ContainerGetBorderWidthMethodInfo
    ResolveSocketMethod "getCanDefault" o = Gtk.Widget.WidgetGetCanDefaultMethodInfo
    ResolveSocketMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveSocketMethod "getChildRequisition" o = Gtk.Widget.WidgetGetChildRequisitionMethodInfo
    ResolveSocketMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveSocketMethod "getChildren" o = Gtk.Container.ContainerGetChildrenMethodInfo
    ResolveSocketMethod "getClip" o = Gtk.Widget.WidgetGetClipMethodInfo
    ResolveSocketMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveSocketMethod "getCompositeName" o = Gtk.Widget.WidgetGetCompositeNameMethodInfo
    ResolveSocketMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveSocketMethod "getDeviceEnabled" o = Gtk.Widget.WidgetGetDeviceEnabledMethodInfo
    ResolveSocketMethod "getDeviceEvents" o = Gtk.Widget.WidgetGetDeviceEventsMethodInfo
    ResolveSocketMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveSocketMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveSocketMethod "getDoubleBuffered" o = Gtk.Widget.WidgetGetDoubleBufferedMethodInfo
    ResolveSocketMethod "getEvents" o = Gtk.Widget.WidgetGetEventsMethodInfo
    ResolveSocketMethod "getFocusChain" o = Gtk.Container.ContainerGetFocusChainMethodInfo
    ResolveSocketMethod "getFocusChild" o = Gtk.Container.ContainerGetFocusChildMethodInfo
    ResolveSocketMethod "getFocusHadjustment" o = Gtk.Container.ContainerGetFocusHadjustmentMethodInfo
    ResolveSocketMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveSocketMethod "getFocusVadjustment" o = Gtk.Container.ContainerGetFocusVadjustmentMethodInfo
    ResolveSocketMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolveSocketMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolveSocketMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolveSocketMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolveSocketMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveSocketMethod "getHasWindow" o = Gtk.Widget.WidgetGetHasWindowMethodInfo
    ResolveSocketMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveSocketMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveSocketMethod "getId" o = SocketGetIdMethodInfo
    ResolveSocketMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
    ResolveSocketMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveSocketMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveSocketMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveSocketMethod "getMarginLeft" o = Gtk.Widget.WidgetGetMarginLeftMethodInfo
    ResolveSocketMethod "getMarginRight" o = Gtk.Widget.WidgetGetMarginRightMethodInfo
    ResolveSocketMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveSocketMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveSocketMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
    ResolveSocketMethod "getModifierStyle" o = Gtk.Widget.WidgetGetModifierStyleMethodInfo
    ResolveSocketMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveSocketMethod "getNoShowAll" o = Gtk.Widget.WidgetGetNoShowAllMethodInfo
    ResolveSocketMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveSocketMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveSocketMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveSocketMethod "getParentWindow" o = Gtk.Widget.WidgetGetParentWindowMethodInfo
    ResolveSocketMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
    ResolveSocketMethod "getPathForChild" o = Gtk.Container.ContainerGetPathForChildMethodInfo
    ResolveSocketMethod "getPlugWindow" o = SocketGetPlugWindowMethodInfo
    ResolveSocketMethod "getPointer" o = Gtk.Widget.WidgetGetPointerMethodInfo
    ResolveSocketMethod "getPreferredHeight" o = Gtk.Widget.WidgetGetPreferredHeightMethodInfo
    ResolveSocketMethod "getPreferredHeightAndBaselineForWidth" o = Gtk.Widget.WidgetGetPreferredHeightAndBaselineForWidthMethodInfo
    ResolveSocketMethod "getPreferredHeightForWidth" o = Gtk.Widget.WidgetGetPreferredHeightForWidthMethodInfo
    ResolveSocketMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveSocketMethod "getPreferredWidth" o = Gtk.Widget.WidgetGetPreferredWidthMethodInfo
    ResolveSocketMethod "getPreferredWidthForHeight" o = Gtk.Widget.WidgetGetPreferredWidthForHeightMethodInfo
    ResolveSocketMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveSocketMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveSocketMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolveSocketMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolveSocketMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolveSocketMethod "getRequisition" o = Gtk.Widget.WidgetGetRequisitionMethodInfo
    ResolveSocketMethod "getResizeMode" o = Gtk.Container.ContainerGetResizeModeMethodInfo
    ResolveSocketMethod "getRootWindow" o = Gtk.Widget.WidgetGetRootWindowMethodInfo
    ResolveSocketMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveSocketMethod "getScreen" o = Gtk.Widget.WidgetGetScreenMethodInfo
    ResolveSocketMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveSocketMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveSocketMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveSocketMethod "getState" o = Gtk.Widget.WidgetGetStateMethodInfo
    ResolveSocketMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveSocketMethod "getStyle" o = Gtk.Widget.WidgetGetStyleMethodInfo
    ResolveSocketMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveSocketMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
    ResolveSocketMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveSocketMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveSocketMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveSocketMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
    ResolveSocketMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
    ResolveSocketMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveSocketMethod "getValignWithBaseline" o = Gtk.Widget.WidgetGetValignWithBaselineMethodInfo
    ResolveSocketMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveSocketMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveSocketMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveSocketMethod "getVisual" o = Gtk.Widget.WidgetGetVisualMethodInfo
    ResolveSocketMethod "getWindow" o = Gtk.Widget.WidgetGetWindowMethodInfo
    ResolveSocketMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
    ResolveSocketMethod "setAllocation" o = Gtk.Widget.WidgetSetAllocationMethodInfo
    ResolveSocketMethod "setAppPaintable" o = Gtk.Widget.WidgetSetAppPaintableMethodInfo
    ResolveSocketMethod "setBorderWidth" o = Gtk.Container.ContainerSetBorderWidthMethodInfo
    ResolveSocketMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
    ResolveSocketMethod "setCanDefault" o = Gtk.Widget.WidgetSetCanDefaultMethodInfo
    ResolveSocketMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveSocketMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveSocketMethod "setClip" o = Gtk.Widget.WidgetSetClipMethodInfo
    ResolveSocketMethod "setCompositeName" o = Gtk.Widget.WidgetSetCompositeNameMethodInfo
    ResolveSocketMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveSocketMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveSocketMethod "setDeviceEnabled" o = Gtk.Widget.WidgetSetDeviceEnabledMethodInfo
    ResolveSocketMethod "setDeviceEvents" o = Gtk.Widget.WidgetSetDeviceEventsMethodInfo
    ResolveSocketMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveSocketMethod "setDoubleBuffered" o = Gtk.Widget.WidgetSetDoubleBufferedMethodInfo
    ResolveSocketMethod "setEvents" o = Gtk.Widget.WidgetSetEventsMethodInfo
    ResolveSocketMethod "setFocusChain" o = Gtk.Container.ContainerSetFocusChainMethodInfo
    ResolveSocketMethod "setFocusChild" o = Gtk.Container.ContainerSetFocusChildMethodInfo
    ResolveSocketMethod "setFocusHadjustment" o = Gtk.Container.ContainerSetFocusHadjustmentMethodInfo
    ResolveSocketMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveSocketMethod "setFocusVadjustment" o = Gtk.Container.ContainerSetFocusVadjustmentMethodInfo
    ResolveSocketMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveSocketMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveSocketMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveSocketMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveSocketMethod "setHasWindow" o = Gtk.Widget.WidgetSetHasWindowMethodInfo
    ResolveSocketMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveSocketMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveSocketMethod "setMapped" o = Gtk.Widget.WidgetSetMappedMethodInfo
    ResolveSocketMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveSocketMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveSocketMethod "setMarginLeft" o = Gtk.Widget.WidgetSetMarginLeftMethodInfo
    ResolveSocketMethod "setMarginRight" o = Gtk.Widget.WidgetSetMarginRightMethodInfo
    ResolveSocketMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveSocketMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveSocketMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveSocketMethod "setNoShowAll" o = Gtk.Widget.WidgetSetNoShowAllMethodInfo
    ResolveSocketMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveSocketMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveSocketMethod "setParentWindow" o = Gtk.Widget.WidgetSetParentWindowMethodInfo
    ResolveSocketMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveSocketMethod "setRealized" o = Gtk.Widget.WidgetSetRealizedMethodInfo
    ResolveSocketMethod "setReallocateRedraws" o = Gtk.Container.ContainerSetReallocateRedrawsMethodInfo
    ResolveSocketMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveSocketMethod "setRedrawOnAllocate" o = Gtk.Widget.WidgetSetRedrawOnAllocateMethodInfo
    ResolveSocketMethod "setResizeMode" o = Gtk.Container.ContainerSetResizeModeMethodInfo
    ResolveSocketMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveSocketMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveSocketMethod "setState" o = Gtk.Widget.WidgetSetStateMethodInfo
    ResolveSocketMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveSocketMethod "setStyle" o = Gtk.Widget.WidgetSetStyleMethodInfo
    ResolveSocketMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
    ResolveSocketMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveSocketMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveSocketMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
    ResolveSocketMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolveSocketMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolveSocketMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolveSocketMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolveSocketMethod "setVisual" o = Gtk.Widget.WidgetSetVisualMethodInfo
    ResolveSocketMethod "setWindow" o = Gtk.Widget.WidgetSetWindowMethodInfo
    ResolveSocketMethod l o = O.MethodResolutionFailed l o

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

#endif

-- signal Socket::plug-added
-- | This signal is emitted when a client is successfully
-- added to the socket.
type SocketPlugAddedCallback =
    IO ()

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

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

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

-- | Wrap the callback into a `GClosure`.
genClosure_SocketPlugAdded :: MonadIO m => SocketPlugAddedCallback -> m (GClosure C_SocketPlugAddedCallback)
genClosure_SocketPlugAdded :: IO () -> m (GClosure C_SocketPlugAddedCallback)
genClosure_SocketPlugAdded cb :: IO ()
cb = IO (GClosure C_SocketPlugAddedCallback)
-> m (GClosure C_SocketPlugAddedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_SocketPlugAddedCallback)
 -> m (GClosure C_SocketPlugAddedCallback))
-> IO (GClosure C_SocketPlugAddedCallback)
-> m (GClosure C_SocketPlugAddedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_SocketPlugAddedCallback
cb' = IO () -> C_SocketPlugAddedCallback
wrap_SocketPlugAddedCallback IO ()
cb
    C_SocketPlugAddedCallback -> IO (FunPtr C_SocketPlugAddedCallback)
mk_SocketPlugAddedCallback C_SocketPlugAddedCallback
cb' IO (FunPtr C_SocketPlugAddedCallback)
-> (FunPtr C_SocketPlugAddedCallback
    -> IO (GClosure C_SocketPlugAddedCallback))
-> IO (GClosure C_SocketPlugAddedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_SocketPlugAddedCallback
-> IO (GClosure C_SocketPlugAddedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `SocketPlugAddedCallback` into a `C_SocketPlugAddedCallback`.
wrap_SocketPlugAddedCallback ::
    SocketPlugAddedCallback ->
    C_SocketPlugAddedCallback
wrap_SocketPlugAddedCallback :: IO () -> C_SocketPlugAddedCallback
wrap_SocketPlugAddedCallback _cb :: IO ()
_cb _ _ = do
    IO ()
_cb 


-- | Connect a signal handler for the [plugAdded](#signal:plugAdded) 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' socket #plugAdded callback
-- @
-- 
-- 
onSocketPlugAdded :: (IsSocket a, MonadIO m) => a -> SocketPlugAddedCallback -> m SignalHandlerId
onSocketPlugAdded :: a -> IO () -> m SignalHandlerId
onSocketPlugAdded 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_SocketPlugAddedCallback
cb' = IO () -> C_SocketPlugAddedCallback
wrap_SocketPlugAddedCallback IO ()
cb
    FunPtr C_SocketPlugAddedCallback
cb'' <- C_SocketPlugAddedCallback -> IO (FunPtr C_SocketPlugAddedCallback)
mk_SocketPlugAddedCallback C_SocketPlugAddedCallback
cb'
    a
-> Text
-> FunPtr C_SocketPlugAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "plug-added" FunPtr C_SocketPlugAddedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [plugAdded](#signal:plugAdded) 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' socket #plugAdded callback
-- @
-- 
-- 
afterSocketPlugAdded :: (IsSocket a, MonadIO m) => a -> SocketPlugAddedCallback -> m SignalHandlerId
afterSocketPlugAdded :: a -> IO () -> m SignalHandlerId
afterSocketPlugAdded 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_SocketPlugAddedCallback
cb' = IO () -> C_SocketPlugAddedCallback
wrap_SocketPlugAddedCallback IO ()
cb
    FunPtr C_SocketPlugAddedCallback
cb'' <- C_SocketPlugAddedCallback -> IO (FunPtr C_SocketPlugAddedCallback)
mk_SocketPlugAddedCallback C_SocketPlugAddedCallback
cb'
    a
-> Text
-> FunPtr C_SocketPlugAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "plug-added" FunPtr C_SocketPlugAddedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data SocketPlugAddedSignalInfo
instance SignalInfo SocketPlugAddedSignalInfo where
    type HaskellCallbackType SocketPlugAddedSignalInfo = SocketPlugAddedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_SocketPlugAddedCallback cb
        cb'' <- mk_SocketPlugAddedCallback cb'
        connectSignalFunPtr obj "plug-added" cb'' connectMode detail

#endif

-- signal Socket::plug-removed
-- | This signal is emitted when a client is removed from the socket.
-- The default action is to destroy the t'GI.Gtk.Objects.Socket.Socket' widget, so if you
-- want to reuse it you must add a signal handler that returns 'P.True'.
type SocketPlugRemovedCallback =
    IO Bool
    -- ^ __Returns:__ 'P.True' to stop other handlers from being invoked.

-- | A convenience synonym for @`Nothing` :: `Maybe` `SocketPlugRemovedCallback`@.
noSocketPlugRemovedCallback :: Maybe SocketPlugRemovedCallback
noSocketPlugRemovedCallback :: Maybe SocketPlugRemovedCallback
noSocketPlugRemovedCallback = Maybe SocketPlugRemovedCallback
forall a. Maybe a
Nothing

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

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

-- | Wrap the callback into a `GClosure`.
genClosure_SocketPlugRemoved :: MonadIO m => SocketPlugRemovedCallback -> m (GClosure C_SocketPlugRemovedCallback)
genClosure_SocketPlugRemoved :: SocketPlugRemovedCallback
-> m (GClosure C_SocketPlugRemovedCallback)
genClosure_SocketPlugRemoved cb :: SocketPlugRemovedCallback
cb = IO (GClosure C_SocketPlugRemovedCallback)
-> m (GClosure C_SocketPlugRemovedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_SocketPlugRemovedCallback)
 -> m (GClosure C_SocketPlugRemovedCallback))
-> IO (GClosure C_SocketPlugRemovedCallback)
-> m (GClosure C_SocketPlugRemovedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_SocketPlugRemovedCallback
cb' = SocketPlugRemovedCallback -> C_SocketPlugRemovedCallback
wrap_SocketPlugRemovedCallback SocketPlugRemovedCallback
cb
    C_SocketPlugRemovedCallback
-> IO (FunPtr C_SocketPlugRemovedCallback)
mk_SocketPlugRemovedCallback C_SocketPlugRemovedCallback
cb' IO (FunPtr C_SocketPlugRemovedCallback)
-> (FunPtr C_SocketPlugRemovedCallback
    -> IO (GClosure C_SocketPlugRemovedCallback))
-> IO (GClosure C_SocketPlugRemovedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_SocketPlugRemovedCallback
-> IO (GClosure C_SocketPlugRemovedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `SocketPlugRemovedCallback` into a `C_SocketPlugRemovedCallback`.
wrap_SocketPlugRemovedCallback ::
    SocketPlugRemovedCallback ->
    C_SocketPlugRemovedCallback
wrap_SocketPlugRemovedCallback :: SocketPlugRemovedCallback -> C_SocketPlugRemovedCallback
wrap_SocketPlugRemovedCallback _cb :: SocketPlugRemovedCallback
_cb _ _ = do
    Bool
result <- SocketPlugRemovedCallback
_cb 
    let result' :: CInt
result' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
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
fromEnum) Bool
result
    CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'


-- | Connect a signal handler for the [plugRemoved](#signal:plugRemoved) 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' socket #plugRemoved callback
-- @
-- 
-- 
onSocketPlugRemoved :: (IsSocket a, MonadIO m) => a -> SocketPlugRemovedCallback -> m SignalHandlerId
onSocketPlugRemoved :: a -> SocketPlugRemovedCallback -> m SignalHandlerId
onSocketPlugRemoved obj :: a
obj cb :: SocketPlugRemovedCallback
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_SocketPlugRemovedCallback
cb' = SocketPlugRemovedCallback -> C_SocketPlugRemovedCallback
wrap_SocketPlugRemovedCallback SocketPlugRemovedCallback
cb
    FunPtr C_SocketPlugRemovedCallback
cb'' <- C_SocketPlugRemovedCallback
-> IO (FunPtr C_SocketPlugRemovedCallback)
mk_SocketPlugRemovedCallback C_SocketPlugRemovedCallback
cb'
    a
-> Text
-> FunPtr C_SocketPlugRemovedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "plug-removed" FunPtr C_SocketPlugRemovedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [plugRemoved](#signal:plugRemoved) 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' socket #plugRemoved callback
-- @
-- 
-- 
afterSocketPlugRemoved :: (IsSocket a, MonadIO m) => a -> SocketPlugRemovedCallback -> m SignalHandlerId
afterSocketPlugRemoved :: a -> SocketPlugRemovedCallback -> m SignalHandlerId
afterSocketPlugRemoved obj :: a
obj cb :: SocketPlugRemovedCallback
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_SocketPlugRemovedCallback
cb' = SocketPlugRemovedCallback -> C_SocketPlugRemovedCallback
wrap_SocketPlugRemovedCallback SocketPlugRemovedCallback
cb
    FunPtr C_SocketPlugRemovedCallback
cb'' <- C_SocketPlugRemovedCallback
-> IO (FunPtr C_SocketPlugRemovedCallback)
mk_SocketPlugRemovedCallback C_SocketPlugRemovedCallback
cb'
    a
-> Text
-> FunPtr C_SocketPlugRemovedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "plug-removed" FunPtr C_SocketPlugRemovedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data SocketPlugRemovedSignalInfo
instance SignalInfo SocketPlugRemovedSignalInfo where
    type HaskellCallbackType SocketPlugRemovedSignalInfo = SocketPlugRemovedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_SocketPlugRemovedCallback cb
        cb'' <- mk_SocketPlugRemovedCallback cb'
        connectSignalFunPtr obj "plug-removed" cb'' connectMode detail

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Socket
type instance O.AttributeList Socket = SocketAttributeList
type SocketAttributeList = ('[ '("appPaintable", Gtk.Widget.WidgetAppPaintablePropertyInfo), '("borderWidth", Gtk.Container.ContainerBorderWidthPropertyInfo), '("canDefault", Gtk.Widget.WidgetCanDefaultPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("child", Gtk.Container.ContainerChildPropertyInfo), '("compositeChild", Gtk.Widget.WidgetCompositeChildPropertyInfo), '("doubleBuffered", Gtk.Widget.WidgetDoubleBufferedPropertyInfo), '("events", Gtk.Widget.WidgetEventsPropertyInfo), '("expand", Gtk.Widget.WidgetExpandPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("isFocus", Gtk.Widget.WidgetIsFocusPropertyInfo), '("margin", Gtk.Widget.WidgetMarginPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginLeft", Gtk.Widget.WidgetMarginLeftPropertyInfo), '("marginRight", Gtk.Widget.WidgetMarginRightPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("noShowAll", Gtk.Widget.WidgetNoShowAllPropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("resizeMode", Gtk.Container.ContainerResizeModePropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("style", Gtk.Widget.WidgetStylePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo), '("window", Gtk.Widget.WidgetWindowPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Socket = SocketSignalList
type SocketSignalList = ('[ '("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), '("plugAdded", SocketPlugAddedSignalInfo), '("plugRemoved", SocketPlugRemovedSignalInfo), '("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, *)])

#endif

-- method Socket::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Socket" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_socket_new" gtk_socket_new :: 
    IO (Ptr Socket)

-- | Create a new empty t'GI.Gtk.Objects.Socket.Socket'.
socketNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Socket
    -- ^ __Returns:__ the new t'GI.Gtk.Objects.Socket.Socket'.
socketNew :: m Socket
socketNew  = IO Socket -> m Socket
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Socket -> m Socket) -> IO Socket -> m Socket
forall a b. (a -> b) -> a -> b
$ do
    Ptr Socket
result <- IO (Ptr Socket)
gtk_socket_new
    Text -> Ptr Socket -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "socketNew" Ptr Socket
result
    Socket
result' <- ((ManagedPtr Socket -> Socket) -> Ptr Socket -> IO Socket
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Socket -> Socket
Socket) Ptr Socket
result
    Socket -> IO Socket
forall (m :: * -> *) a. Monad m => a -> m a
return Socket
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Socket::add_id
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket_"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSocket" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "window"
--           , argType = TBasicType TULong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the Window of a client participating in the XEMBED protocol."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_socket_add_id" gtk_socket_add_id :: 
    Ptr Socket ->                           -- socket_ : TInterface (Name {namespace = "Gtk", name = "Socket"})
    CULong ->                               -- window : TBasicType TULong
    IO ()

-- | Adds an XEMBED client, such as a t'GI.Gtk.Objects.Plug.Plug', to the t'GI.Gtk.Objects.Socket.Socket'.  The
-- client may be in the same process or in a different process.
-- 
-- To embed a t'GI.Gtk.Objects.Plug.Plug' in a t'GI.Gtk.Objects.Socket.Socket', you can either create the
-- t'GI.Gtk.Objects.Plug.Plug' with @gtk_plug_new (0)@, call
-- 'GI.Gtk.Objects.Plug.plugGetId' to get the window ID of the plug, and then pass that to the
-- 'GI.Gtk.Objects.Socket.socketAddId', or you can call 'GI.Gtk.Objects.Socket.socketGetId' to get the
-- window ID for the socket, and call 'GI.Gtk.Objects.Plug.plugNew' passing in that
-- ID.
-- 
-- The t'GI.Gtk.Objects.Socket.Socket' must have already be added into a toplevel window
--  before you can make this call.
socketAddId ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket_@/: a t'GI.Gtk.Objects.Socket.Socket'
    -> CULong
    -- ^ /@window@/: the Window of a client participating in the XEMBED protocol.
    -> m ()
socketAddId :: a -> SignalHandlerId -> m ()
socketAddId socket_ :: a
socket_ window :: SignalHandlerId
window = 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 Socket
socket_' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket_
    Ptr Socket -> SignalHandlerId -> IO ()
gtk_socket_add_id Ptr Socket
socket_' SignalHandlerId
window
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket_
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SocketAddIdMethodInfo
instance (signature ~ (CULong -> m ()), MonadIO m, IsSocket a) => O.MethodInfo SocketAddIdMethodInfo a signature where
    overloadedMethod = socketAddId

#endif

-- method Socket::get_id
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket_"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSocket." , 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_socket_get_id" gtk_socket_get_id :: 
    Ptr Socket ->                           -- socket_ : TInterface (Name {namespace = "Gtk", name = "Socket"})
    IO CULong

-- | Gets the window ID of a t'GI.Gtk.Objects.Socket.Socket' widget, which can then
-- be used to create a client embedded inside the socket, for
-- instance with 'GI.Gtk.Objects.Plug.plugNew'.
-- 
-- The t'GI.Gtk.Objects.Socket.Socket' must have already be added into a toplevel window
-- before you can make this call.
socketGetId ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket_@/: a t'GI.Gtk.Objects.Socket.Socket'.
    -> m CULong
    -- ^ __Returns:__ the window ID for the socket
socketGetId :: a -> m SignalHandlerId
socketGetId socket_ :: a
socket_ = 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 Socket
socket_' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket_
    SignalHandlerId
result <- Ptr Socket -> IO SignalHandlerId
gtk_socket_get_id Ptr Socket
socket_'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
socket_
    SignalHandlerId -> IO SignalHandlerId
forall (m :: * -> *) a. Monad m => a -> m a
return SignalHandlerId
result

#if defined(ENABLE_OVERLOADING)
data SocketGetIdMethodInfo
instance (signature ~ (m CULong), MonadIO m, IsSocket a) => O.MethodInfo SocketGetIdMethodInfo a signature where
    overloadedMethod = socketGetId

#endif

-- method Socket::get_plug_window
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "socket_"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Socket" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSocket." , 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_socket_get_plug_window" gtk_socket_get_plug_window :: 
    Ptr Socket ->                           -- socket_ : TInterface (Name {namespace = "Gtk", name = "Socket"})
    IO (Ptr Gdk.Window.Window)

-- | Retrieves the window of the plug. Use this to check if the plug has
-- been created inside of the socket.
-- 
-- /Since: 2.14/
socketGetPlugWindow ::
    (B.CallStack.HasCallStack, MonadIO m, IsSocket a) =>
    a
    -- ^ /@socket_@/: a t'GI.Gtk.Objects.Socket.Socket'.
    -> m (Maybe Gdk.Window.Window)
    -- ^ __Returns:__ the window of the plug if
    -- available, or 'P.Nothing'
socketGetPlugWindow :: a -> m (Maybe Window)
socketGetPlugWindow socket_ :: a
socket_ = 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 Socket
socket_' <- a -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
socket_
    Ptr Window
result <- Ptr Socket -> IO (Ptr Window)
gtk_socket_get_plug_window Ptr Socket
socket_'
    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
socket_
    Maybe Window -> IO (Maybe Window)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Window
maybeResult

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

#endif